Skip to content

Commit

Permalink
solve clashes between repo and local folder
Browse files Browse the repository at this point in the history
  • Loading branch information
ogurses committed Jul 20, 2023
2 parents b78dfc4 + acbf838 commit f5edae1
Show file tree
Hide file tree
Showing 8 changed files with 34 additions and 39 deletions.
8 changes: 5 additions & 3 deletions src/int_recom/recom_extra.F90
Original file line number Diff line number Diff line change
Expand Up @@ -271,10 +271,12 @@ subroutine Atm_input(mesh)
if (useAeolianN) then
i=1 ! A single time entry
DustNfilename = trim(REcoMDataPath)//'AeolianNitrogenDep.nc'
if (yearnew .lt. 2010) then
Nvari = 'NDep'//cyearnew
else
if (yearnew .gt. 2009) then
Nvari = 'NDep2009'
else if (yearnew .lt. 1850) then
Nvari = 'NDep1850'
else
Nvari = 'NDep'//cyearnew
endif

if (mype==0) write(*,*) 'Updating Nitrogen deposition data for month ', i
Expand Down
2 changes: 1 addition & 1 deletion src/int_recom/recom_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ subroutine REcoM_Forcing(zNodes, n, Nn, state, SurfSW, Loc_slp, Temp, Sali, PAR,
Real(kind=8) :: REcoM_O2(1) ! [mmol/m3] Conc of O2 in the surface water, used to calculate O2 flux

! Subroutine REcoM_sms
Real(kind=8),dimension(mesh%nl-1,bgc_num) :: sms, aux ! matrix that entail changes in tracer concentrations
Real(kind=8),dimension(mesh%nl-1,bgc_num) :: sms ! matrix that entail changes in tracer concentrations

!Diagnostics
integer :: idiags,n,k
Expand Down
28 changes: 6 additions & 22 deletions src/int_recom/recom_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -278,30 +278,14 @@ subroutine recom_init(mesh)
!!#endif
!tr_arr(:,:,24) ! tracer 24 = Oxy ! read from the file

!if (REcoM_Second_Zoo) then
if (REcoM_Second_Zoo) then
tr_arr(:,:,25) = tiny ! tracer 25 = Zoo2N
tr_arr(:,:,26) = tiny * Redfield ! tracer 26 = Zoo2C
!endif



if (REcoM_Second_Zoo) then
! if (REcoM_Second_Zoo .and. zoo2_initial_field) then
! tracer(:,:,27) = tiny ! tracer 26 = DetZ2N
! tracer(:,:,28) = tiny ! tracer 27 = DetZ2C
! tracer(:,:,29) = tiny ! tracer 28 = DetZ2Si
! tracer(:,:,30) = tiny ! tracer 29 = DetZ2Calc
! else
! tracer(:,:,25) = tiny ! tracer 24 = Zoo2N
! tracer(:,:,26) = tiny ! tracer 25 = Zoo2C
tracer(:,:,27) = tiny ! tracer 26 = DetZ2N
tracer(:,:,28) = tiny ! tracer 27 = DetZ2C
tracer(:,:,29) = tiny ! tracer 28 = DetZ2Si
tracer(:,:,30) = tiny ! tracer 29 = DetZ2Calc
! endif
endif


tr_arr(:,:,27) = tiny ! tracer 26 = DetZ2N
tr_arr(:,:,28) = tiny ! tracer 27 = DetZ2C
tr_arr(:,:,29) = tiny ! tracer 28 = DetZ2Si
tr_arr(:,:,30) = tiny ! tracer 29 = DetZ2Calc
endif

if (ciso) then
tr_arr(:,:,27) = (1. + 0.001 * (2.3 - 0.06 * tr_arr(:,:,3))) * tr_arr(:,:,4) ! DIC_13, GLODAP2 > 500 m
Expand Down
3 changes: 2 additions & 1 deletion src/int_recom/recom_main.F90
Original file line number Diff line number Diff line change
Expand Up @@ -165,6 +165,7 @@ subroutine recom(mesh)
end if

GloHplus(n) = ph(1) ! hplus

AtmFeInput(n) = FeDust
AtmNInput(n) = NDust
! DenitBen(n) = LocDenit
Expand Down Expand Up @@ -278,7 +279,7 @@ subroutine bio_fluxes(mesh)

! Alkalinity restoring to climatology

if (.not. restore_alkalinity) return
if (.not. restore_alkalinity) return

do n=1, myDim_nod2D+eDim_nod2D
relax_alk(n)=surf_relax_Alk*(Alk_surf(n)-tr_arr(1,n,2+ialk)) ! 1 temp, 2 salt
Expand Down
7 changes: 4 additions & 3 deletions src/int_recom/recom_sms.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
subroutine REcoM_sms(n,Nn,state,thick,recipthick,SurfSR,sms,Temp,SinkVel,zF,PAR, mesh)
subroutine REcoM_sms(n,Nn,state,thick,recipthick,SurfSR,sms,Temp,zF,PAR, mesh)

use REcoM_declarations
use REcoM_LocVar
Expand Down Expand Up @@ -33,7 +33,6 @@ subroutine REcoM_sms(n,Nn,state,thick,recipthick,SurfSR,sms,Temp,SinkVel,zF,PAR,

real(kind=8),dimension(mesh%nl-1,bgc_num),intent(inout) :: sms !< Source-Minus-Sinks term
real(kind=8),dimension(mesh%nl-1) ,intent(in) :: Temp !< [degrees C] Ocean temperature
real(kind=8),dimension(mesh%nl,4) ,intent(in) :: SinkVel

real(kind=8),dimension(mesh%nl) ,intent(in) :: zF !< [m] Depth of fluxes
real(kind=8),dimension(mesh%nl-1),intent(inout) :: PAR
Expand All @@ -47,6 +46,7 @@ subroutine REcoM_sms(n,Nn,state,thick,recipthick,SurfSR,sms,Temp,SinkVel,zF,PAR,
real(kind=8) :: Fc !< Flux of labile C into sediment, used for denitrification calculation [umolC/cm2/s]
real(kind=8) :: recip_hetN_plus !< MB's addition to heterotrophic respiration
real(kind=8) :: recip_res_het !< [day] Reciprocal of respiration by heterotrophs and mortality (loss to detritus)
real(kind=8) :: Sink_Vel
real(kind=8) :: aux
integer :: k,step,ii, idiags,n
real(kind=8) :: &
Expand Down Expand Up @@ -162,7 +162,8 @@ subroutine REcoM_sms(n,Nn,state,thick,recipthick,SurfSR,sms,Temp,SinkVel,zF,PAR,
PhyCalc= max(tiny,state(k,iphycal) + sms(k,iphycal))
DetCalc= max(tiny,state(k,idetcal) + sms(k,idetcal))

calc_diss = calc_diss_rate * SinkVel(k,ivdet) /20.d0 ! Dissolution rate of CaCO3 scaled by the sinking velocity at the current depth 0.005714 !20.d0/3500.d0
Sink_Vel = Vdet_a* abs(zF(k)) + Vdet
calc_diss = calc_diss_rate * Sink_Vel /20.d0
calc_diss2 = calc_diss_rate2 ! Dissolution rate of CaCO3 for seczoo

quota = PhyN / PhyC ! include variability of the N: C ratio, cellular chemical composition
Expand Down
8 changes: 4 additions & 4 deletions src/io_meandata.F90
Original file line number Diff line number Diff line change
Expand Up @@ -353,22 +353,22 @@ subroutine ini_mean_io(mesh)

CASE ('benN ')
if (use_REcoM) then
call def_stream(nod2D, myDim_nod2D, 'benN','Benthos Nitrogen','mmol/m2', Benthos(:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
call def_stream(nod2D, myDim_nod2D, 'benN','Benthos Nitrogen','mmol', Benthos(:,1), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
end if

CASE ('benC ')
if (use_REcoM) then
call def_stream(nod2D, myDim_nod2D, 'benC','Benthos Carbon','mmol/m2', Benthos(:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
call def_stream(nod2D, myDim_nod2D, 'benC','Benthos Carbon','mmol', Benthos(:,2), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
end if

CASE ('benSi ')
if (use_REcoM) then
call def_stream(nod2D, myDim_nod2D, 'benSi','Benthos silicon','mmol/m2', Benthos(:,3), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
call def_stream(nod2D, myDim_nod2D, 'benSi','Benthos silicon','mmol', Benthos(:,3), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
end if

CASE ('benCalc ')
if (use_REcoM) then
call def_stream(nod2D, myDim_nod2D, 'benCalc','Benthos calcite','mmol/m2', Benthos(:,4), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
call def_stream(nod2D, myDim_nod2D, 'benCalc','Benthos calcite','mmol', Benthos(:,4), io_list(i)%freq, io_list(i)%unit, io_list(i)%precision, mesh)
end if
! ciso
CASE ('benC_13 ')
Expand Down
8 changes: 4 additions & 4 deletions src/oce_setup_step.F90
Original file line number Diff line number Diff line change
Expand Up @@ -281,11 +281,11 @@ SUBROUTINE array_setup(mesh)
! ================
#if defined(__recom)
if(use_REcoM) then
if (restore_alkalinity) then
!if (restore_alkalinity) then
allocate(Alk_surf(node_size))
allocate(relax_alk(node_size))
allocate(virtual_alk(node_size))
endif
!endif
end if
#endif
! =================
Expand Down Expand Up @@ -450,11 +450,11 @@ SUBROUTINE array_setup(mesh)
! ================
#if defined(__recom)
if(use_REcoM) then
if (restore_alkalinity) then
!if (restore_alkalinity) then
Alk_surf=0.0_WP
relax_alk=0.0_WP
virtual_alk=0.0_WP
endif
!endif
end if
#endif
! init field for pressure force
Expand Down
9 changes: 8 additions & 1 deletion src/recom_sinking.F90
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,13 @@ subroutine recom_sinking_new(tr_num,mesh)
tracer_id(tr_num)==1015 ) then !idchl

Vsink = VDia

elseif(tracer_id(tr_num)==1025 .or. & !idetz2n
tracer_id(tr_num)==1026 .or. & !idetz2c
tracer_id(tr_num)==1027 .or. & !idetz2si
tracer_id(tr_num)==1028 ) then !idetz2calc

Vsink = VDet_zoo2
end if

if (Vsink .gt. 0.1) then ! No sinking if Vsink < 0.1 m/day
Expand Down Expand Up @@ -97,7 +104,7 @@ subroutine recom_sinking_new(tr_num,mesh)
tracer_id(tr_num)==1026 .or. & !idetz2c
tracer_id(tr_num)==1027 .or. & !idetz2si
tracer_id(tr_num)==1028 ) then !idetz2calc
Wvel_flux(nz) = -VDet_zoo2/SecondsPerDay ! --> VDet_zoo2
Wvel_flux(nz) = -Vsink/SecondsPerDay ! --> VDet_zoo2

endif
end do
Expand Down

0 comments on commit f5edae1

Please sign in to comment.