Skip to content

Commit

Permalink
iHAMOCC kwrbioz off - enable remin and primary prod throughout full w…
Browse files Browse the repository at this point in the history
…ater column (#367)

* introduce new logical

* disentangle processes according to kwrbioz

* keep phyto- and zooplankton mortality in primary production loop

* simplify and fix cisonew in remin

* add lkwrbioz_off switch to namelist definition file

* Put default lkwrbioz=.false. to recover former master; REGRESSION TESTED
  • Loading branch information
jmaerz authored Jul 12, 2024
1 parent 5d62993 commit 07d6219
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 21 deletions.
10 changes: 10 additions & 0 deletions cime_config/namelist_definition_blom.xml
Original file line number Diff line number Diff line change
Expand Up @@ -3653,6 +3653,16 @@
<desc>Switch for cyano-bluefix in euphotic zone only</desc>
</entry>

<entry id="lkwrbioz_off">
<type>logical</type>
<category>bgcnml</category>
<group>bgcnml</group>
<values>
<value>.false.</value>
</values>
<desc>Switch for primary production and remineralization throughout the whole water column</desc>
</entry>

<entry id="do_oalk">
<type>logical</type>
<category>bgcnml</category>
Expand Down
3 changes: 2 additions & 1 deletion hamocc/mo_control_bgc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,8 @@ module mo_control_bgc
logical :: do_oalk = .false. ! apply ocean alkalinization
logical :: with_dmsph = .false. ! apply DMS with pH dependence
logical :: use_M4AGO = .false. ! run with M4AGO settling scheme
logical :: leuphotic_cya = .true. ! allow cyanobacteria to grow only in euphotic zone
logical :: leuphotic_cya = .true. ! allow cyanobacteria to grow only in euphotic zone
logical :: lkwrbioz_off = .false. ! if true, allow remin and primary prod throughout full water column
integer :: sedspin_yr_s = -1 ! start year for sediment spin-up
integer :: sedspin_yr_e = -1 ! end year for sediment spin-up
integer :: sedspin_ncyc = -1 ! sediment spin-up sub-cycles
Expand Down
4 changes: 2 additions & 2 deletions hamocc/mo_hamocc_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ subroutine hamocc_init(read_rest,rstfnm_hamocc)
do_sedspinup,sedspin_yr_s,sedspin_yr_e,sedspin_ncyc, &
dtb,dtbgc,io_stdo_bgc,ldtbgc, &
ldtrunbgc,ndtdaybgc,with_dmsph,l_3Dvarsedpor,use_M4AGO, &
do_ndep_coupled,leuphotic_cya,do_n2onh3_coupled, &
do_ndep_coupled,leuphotic_cya,lkwrbioz_off,do_n2onh3_coupled, &
ocn_co2_type, use_sedbypass, use_BOXATM, use_BROMO,use_extNcycle
use mo_param1_bgc, only: ks,init_por2octra_mapping
use mo_param_bgc, only: ini_parambgc
Expand Down Expand Up @@ -81,7 +81,7 @@ subroutine hamocc_init(read_rest,rstfnm_hamocc)
& do_sedspinup,sedspin_yr_s,sedspin_yr_e,sedspin_ncyc, &
& inidic,inialk,inipo4,inioxy,inino3,inisil,inid13c,inid14c,swaclimfile, &
& with_dmsph,pi_ph_file,l_3Dvarsedpor,sedporfile,ocn_co2_type,use_M4AGO, &
& leuphotic_cya, do_ndep_coupled,do_n2onh3_coupled
& leuphotic_cya, do_ndep_coupled,do_n2onh3_coupled,lkwrbioz_off
!
! --- Set io units and some control parameters
!
Expand Down
64 changes: 47 additions & 17 deletions hamocc/mo_ocprod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
use mo_control_bgc, only: dtb,io_stdo_bgc,with_dmsph, &
use_BROMO,use_AGG,use_PBGC_OCNP_TIMESTEP,use_FB_BGC_OCE, &
use_AGG,use_cisonew,use_natDIC, use_WLIN,use_sedbypass,use_M4AGO, &
use_extNcycle
use_extNcycle,lkwrbioz_off
use mo_vgrid, only: dp_min,dp_min_sink,k0100,k0500,k1000,k2000,k4000,kwrbioz,ptiestu
use mo_vgrid, only: kmle
use mo_clim_swa, only: swa_clim
Expand Down Expand Up @@ -250,7 +250,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
absorption = 1.
absorption_uv = 1.

vloop: do k = 1,kwrbioz(i,j)
vloop: do k = 1,merge(kpke,kwrbioz(i,j),lkwrbioz_off)

if(pddpo(i,j,k) > 0.0) then

Expand Down Expand Up @@ -305,7 +305,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp

loop1: do j = 1,kpje
do i = 1,kpie
do k = 1,kwrbioz(i,j)
do k = 1,merge(kpke,kwrbioz(i,j),lkwrbioz_off)

if(pddpo(i,j,k) > dp_min .and. omask(i,j) > 0.5) then

Expand Down Expand Up @@ -348,18 +348,21 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
xn = xa/(1.+pho*avphy/(xa+bkphy))
phosy = max(0.,xa-xn)
endif
phosy = MERGE(avdic/rcar, phosy, avdic <= rcar*phosy) ! limit phosy by available DIC
phosy = merge(avdic/rcar, phosy, avdic <= rcar*phosy) ! limit phosy by available DIC
ya = avphy+phosy
yn = (ya+grazra*avgra*phytomi/(avphy+bkzoo))/(1.+grazra*avgra/(avphy+bkzoo))
grazing = max(0.,ya-yn)
graton = epsher*(1.-zinges)*grazing
gratpoc = (1.-epsher)*grazing
grawa = epsher*zinges*grazing
bacfra=remido*ocetra(i,j,k,idoc)

phythresh = max(0.,(ocetra(i,j,k,iphy)-2.*phytomi))
zoothresh = max(0.,(ocetra(i,j,k,izoo)-2.*grami))
phymor = dyphy*phythresh
zoothresh = max(0.,(ocetra(i,j,k,izoo)-2.*grami))
if (lkwrbioz_off) then
bacfra = 0.
else
bacfra = remido*ocetra(i,j,k,idoc)
endif
exud = gammap*phythresh
zoomor = spemor*zoothresh*zoothresh ! *10 compared to linear in tropics (tinka)
excdoc = gammaz*zoothresh ! excretion of doc by zooplankton
Expand Down Expand Up @@ -402,8 +405,13 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
grawa13 = epsher*zinges*grazing13
grawa14 = epsher*zinges*grazing14

bacfra13 = remido*ocetra(i,j,k,idoc13)
bacfra14 = remido*ocetra(i,j,k,idoc14)
if (lkwrbioz_off) then
bacfra13 = 0.
bacfra14 = 0.
else
bacfra13 = remido*ocetra(i,j,k,idoc13)
bacfra14 = remido*ocetra(i,j,k,idoc14)
endif

phymor13 = phymor*rphy13
phymor14 = phymor*rphy14
Expand Down Expand Up @@ -440,8 +448,12 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
dms_ph = 1.
endif
dmsprod = (dmsp5*delsil+dmsp4*delcar)*(1.+1./(temp+dmsp1)**2)*dms_ph
dms_bac = dmsp3*abs(temp+3.)*ocetra(i,j,k,idms) &
& *(ocetra(i,j,k,idms)/(dmsp6+ocetra(i,j,k,idms)))
if (lkwrbioz_off) then
dms_bac = 0.
else
dms_bac = dmsp3*abs(temp+3.)*ocetra(i,j,k,idms) &
& *(ocetra(i,j,k,idms)/(dmsp6+ocetra(i,j,k,idms)))
endif
dms_uv = dmsp2*phofa/pi_alpha*ocetra(i,j,k,idms)

dtr = bacfra-phosy+graton+ecan*zoomor
Expand Down Expand Up @@ -494,10 +506,14 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
ocetra(i,j,k,inatalkali) = ocetra(i,j,k,inatalkali)-2.*delcar-(rnit+1)*dtr
ocetra(i,j,k,inatcalc) = ocetra(i,j,k,inatcalc)+delcar
endif
if (use_M4AGO) then
opalrem = dremopal*opal_remin_q10**((ptho(i,j,k)-opal_remin_Tref)/10.)*ocetra(i,j,k,iopal)
if (lkwrbioz_off) then
opalrem = 0.
else
opalrem = dremopal*ocetra(i,j,k,iopal)
if (use_M4AGO) then
opalrem = dremopal*opal_remin_q10**((ptho(i,j,k)-opal_remin_Tref)/10.)*ocetra(i,j,k,iopal)
else
opalrem = dremopal*ocetra(i,j,k,iopal)
endif
endif
ocetra(i,j,k,isilica) = ocetra(i,j,k,isilica)-delsil+opalrem
ocetra(i,j,k,iopal) = ocetra(i,j,k,iopal)+delsil-opalrem
Expand Down Expand Up @@ -595,7 +611,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp

loop2: do j = 1,kpje
do i = 1,kpie
do k = kwrbioz(i,j)+1,kpke
do k = merge(1,kwrbioz(i,j)+1,lkwrbioz_off),kpke
if(pddpo(i,j,k) > dp_min .and. omask(i,j) > 0.5) then

if (use_AGG) then
Expand All @@ -621,6 +637,16 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
sterzo13 = sterzo*rzoo13
sterzo14 = sterzo*rzoo14
endif

if (lkwrbioz_off) then ! dying before in PP loop
sterph = 0.
sterzo = 0.
sterph13 = 0.
sterph14 = 0.
sterzo13 = 0.
sterzo14 = 0.
endif

ocetra(i,j,k,iphy) = ocetra(i,j,k,iphy)-sterph
ocetra(i,j,k,izoo) = ocetra(i,j,k,izoo)-sterzo
if (use_cisonew) then
Expand Down Expand Up @@ -654,6 +680,10 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
phyrem = min(0.5*dyphy*phythresh, 0.33*ocetra(i,j,k,ioxygen)/ro2utammo)
endif

if (lkwrbioz_off) then ! dying before in PP loop
phyrem = 0.
endif

if (use_cisonew) then
pocrem13 = pocrem*rdet13
pocrem14 = pocrem*rdet14
Expand Down Expand Up @@ -782,7 +812,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
!$OMP PARALLEL DO PRIVATE(remin,remin2o,dz,avmass,avnos,rem13,rem14,i,k)
loop3: do j = 1,kpje
do i = 1,kpie
do k = kwrbioz(i,j)+1,kpke
do k = merge(1,kwrbioz(i,j)+1,lkwrbioz_off),kpke
if(omask(i,j) > 0.5) then
if(ocetra(i,j,k,ioxygen) < 5.e-7 .and. pddpo(i,j,k) > dp_min) then
if (use_AGG) then
Expand Down Expand Up @@ -875,7 +905,7 @@ subroutine ocprod(kpie,kpje,kpke,kbnd,pdlxp,pdlyp,pddpo,omask,ptho,pi_ph,psao,pp
!$OMP PARALLEL DO PRIVATE(remin,avmass,avnos,rem13,rem14,i,k)
loop4: do j = 1,kpje
do i = 1,kpie
do k = kwrbioz(i,j)+1,kpke
do k = merge(1,kwrbioz(i,j)+1,lkwrbioz_off),kpke
if(omask(i,j) > 0.5 .and. pddpo(i,j,k) > dp_min) then
if(ocetra(i,j,k,ioxygen) < 5.e-7 .and. ocetra(i,j,k,iano3) < 3.e-6) then

Expand Down
4 changes: 3 additions & 1 deletion hamocc/mo_param_bgc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ module mo_param_bgc
do_ndep,do_oalk,do_rivinpt,do_sedspinup,l_3Dvarsedpor, &
use_BOXATM,use_CFC,use_PBGC_CK_TIMESTEP, &
use_sedbypass,with_dmsph,use_PBGC_OCNP_TIMESTEP,ocn_co2_type,use_M4AGO,&
leuphotic_cya,do_ndep_coupled,do_n2onh3_coupled,use_extNcycle
leuphotic_cya,do_ndep_coupled,do_n2onh3_coupled,use_extNcycle, &
lkwrbioz_off
use mod_xc, only: mnproc

implicit none
Expand Down Expand Up @@ -834,6 +835,7 @@ subroutine write_parambgc()
call cinfo_add_entry('do_sedspinup', do_sedspinup)
call cinfo_add_entry('l_3Dvarsedpor', l_3Dvarsedpor)
call cinfo_add_entry('leuphotic_cya', leuphotic_cya)
call cinfo_add_entry('lkwrbioz_off', lkwrbioz_off)
call cinfo_add_entry('use_M4AGO', use_M4AGO)
if (use_extNcycle) then
call cinfo_add_entry('do_ndep_coupled', do_ndep_coupled)
Expand Down

0 comments on commit 07d6219

Please sign in to comment.