From 683b632e40e334a638a667e3724a93d832337c3c Mon Sep 17 00:00:00 2001 From: InkyANB Date: Wed, 22 Nov 2023 18:04:22 +0000 Subject: [PATCH 1/7] New code for EcoGEnIE 1.1 (Naidoo-Bagwell et al., GMD, 2023), which includes the implementation of phytoplankton functional groups diatoms, picophytoplankton and eukaryotes On branch DEV_GMD23 new file: genie-ecogem/data/input/3Diat_4ZP_PiEu.eco modified: genie-ecogem/src/fortran/ecogem.f90 modified: genie-ecogem/src/fortran/ecogem_box.f90 modified: genie-ecogem/src/fortran/ecogem_data.f90 modified: genie-ecogem/src/fortran/ecogem_lib.f90 modified: genie-ecogem/src/fortran/initialise_ecogem.f90 new file: genie-main/configs/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config modified: genie-main/src/xml-config/xml/definition.xml new folder: genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 --- genie-ecogem/data/input/3Diat_4ZP_PiEu.eco | 45 ++++ genie-ecogem/src/fortran/ecogem.f90 | 39 +++- genie-ecogem/src/fortran/ecogem_box.f90 | 26 ++- genie-ecogem/src/fortran/ecogem_data.f90 | 205 +++++++---------- genie-ecogem/src/fortran/ecogem_lib.f90 | 23 +- .../src/fortran/initialise_ecogem.f90 | 9 +- ...fin.CBE.worjh2.BASESFeTDTLSi.Albani.config | 173 ++++++++++++++ genie-main/src/xml-config/xml/definition.xml | 71 +++++- .../3Diat_4ZP_PiEu.eco | 45 ++++ .../Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 | 212 ++++++++++++++++++ .../EcoGEnIE1.1_phys | 184 +++++++++++++++ .../EcoGEnIE1.1_phys_eco | 212 ++++++++++++++++++ .../Naidoo-Bagwell_et_al.GMD.2023/NoDiatom | 212 ++++++++++++++++++ .../diat.worjh2.Albani | 193 ++++++++++++++++ ...fin.CBE.worjh2.BASESFeTDTLSi.Albani.config | 173 ++++++++++++++ .../Naidoo-Bagwell_et_al.GMD.2023/readme.txt | 48 ++++ 16 files changed, 1721 insertions(+), 149 deletions(-) create mode 100644 genie-ecogem/data/input/3Diat_4ZP_PiEu.eco create mode 100644 genie-main/configs/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys_eco create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/NoDiatom create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/diat.worjh2.Albani create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config create mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt diff --git a/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco b/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco new file mode 100644 index 000000000..2231035f5 --- /dev/null +++ b/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco @@ -0,0 +1,45 @@ + + 01 02 03 + \/ \/ \/ + +-START-OF-DATA- + Diatom 2.00 1 + Diatom 20.00 1 + Diatom 200.00 1 + Picoplankton 0.6 1 + Picoplankton 2.00 1 + Eukaryote 20.00 1 + Eukaryote 200.00 1 + Zooplankton 6.00 1 + Zooplankton 20.00 1 + Zooplankton 200.00 1 + Zooplankton 2000.00 1 +-END-OF-DATA- + + /\ /\ /\ + 01 02 03 + +DATA FORMAT AND ORDER +--------------------- + +COLUMN #01: plankton functional type name +COLUMN #02: plankton diameter (micrometers) +COLUMN #03: number of randomised replicates + +INFO: TRACER ASSIGNMENT RULES +----------------------------- +Plankton functional type one of: Prochlorococcus + Synechococcus + Picoeukaryote + Picoplankton + Diatom + Coccolithophore + Diazotroph + Eukaryote + Phytoplankton + Zooplankton + Mixotroph + + + + diff --git a/genie-ecogem/src/fortran/ecogem.f90 b/genie-ecogem/src/fortran/ecogem.f90 index c10de2d25..05da3ebc5 100644 --- a/genie-ecogem/src/fortran/ecogem.f90 +++ b/genie-ecogem/src/fortran/ecogem.f90 @@ -398,6 +398,11 @@ subroutine ecogem( & elseif (io.eq.iChlo) then assimilated(io,:) = 0.0 ! don't assimilate chlorophyll endif + do jpred=1,npmax ! JDW - check do loop is needed + if (io.eq.iSili .and. pft(jpred).eq.'zooplankton') then ! .and. silicify(:).eq.0.0) then + assimilated(io,jpred) = 0.0 ! don't assimilate Si if not selected - Scott April 2019 + endif + enddo ! Aaron Diatom 23 unassimilated(:,:) = 1.0 - assimilated(:,:) enddo !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc @@ -447,7 +452,8 @@ subroutine ecogem( & io=nut2quota(ii) dbiomassdt(io,:) = dbiomassdt(io,:) + up_inorg(ii ,:) * BioC(:) enddo - + ! Take into account nitrogen fixation here scaled with dbiomass in phosphorus - Fanny Jun20 + dbiomassdt(iNitr,:) = merge(dbiomassdt(iPhos,:)*40.0,dbiomassdt(iNitr,:),pft.eq.'diazotroph') ! Aaron Diatom 23 if (eco_uptake_fluxes) then do io=1,iomax AP_uptake(io,:) = dbiomassdt(io,:) @@ -536,8 +542,8 @@ subroutine ecogem( & !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc orgbGraz(:,:) = 0.0 - - do io=1,iomax + do io=1,iomax !! Be aware this calculates also for Si "OM" - Fanny/Jamie - Jun19 + ! mortality dorgmatdt(io,1) = dorgmatdt(io,1) + sum(loc_biomass(io,:) * mortality(:) * beta_mort(:) ) ! fraction to DOM dorgmatdt(io,2) = dorgmatdt(io,2) + sum(loc_biomass(io,:) * mortality(:) * beta_mort_1(:)) ! fraction to POM @@ -761,6 +767,7 @@ subroutine ecogem( & if (nquota) dum_egbg_sfcpart(is_PON ,:,:,:) = orgmat_flux(iNitr,2,:,:,:) / 1.0e3 / conv_m3_kg ! convert back to mol kg^{-1} s^{-1} if (pquota) dum_egbg_sfcpart(is_POP ,:,:,:) = orgmat_flux(iPhos,2,:,:,:) / 1.0e3 / conv_m3_kg ! convert back to mol kg^{-1} s^{-1} if (fquota) dum_egbg_sfcpart(is_POFe ,:,:,:) = orgmat_flux(iIron,2,:,:,:) / 1.0e3 / conv_m3_kg ! convert back to mol kg^{-1} s^{-1} + if (squota) dum_egbg_sfcpart(is_opal ,:,:,:) = (orgmat_flux(iSili,1,:,:,:) + orgmat_flux(iSili,2,:,:,:)) / 1.0e3 / conv_m3_kg ! convert back to mol kg^{-1} s^{-1} ! FMM/JDW June 2019, "DOSi + POSi" Aaron Diatom 23 !ckc Isotopes particulate dum_egbg_sfcpart(is_POC_13C,:,:,:) = orgmatiso_flux(iCarb13C,2,:,:,:) / 1.0e3 / conv_m3_kg ! convert back to mol kg^{-1} s^{-1} @@ -796,10 +803,30 @@ subroutine ecogem( & dum_egbg_sfcdiss(io_DIC_13C ,:,:,:) = dum_egbg_sfcdiss(io_DIC_13C,:,:,:) - 1.0 * dum_egbg_sfcpart(is_CaCO3_13C,:,:,:) endif - ! set initial values for protected fraction of POM and CaCO3 - dum_egbg_sfcpart(is_POC_frac2 ,:,:,n_k) = par_bio_remin_POC_frac2 - dum_egbg_sfcpart(is_CaCO3_frac2,:,:,n_k) = par_bio_remin_CaCO3_frac2 + ! set initial values for protected fraction of POM and CaCO3 Aaron Diatom 23 + ! Added ballast parameterisation - Fanny, Aug20 + ! NEED TO MAKE CARRYING COEF EXPLICIT (HARD CODING HERE BECAUSE WANT TO FIND A WAY TO DEFINE THEM ONLY ONE) - Fanny Aug20 + ! Changed frac2 modification to be for imld:n_k rather than n_k + if (ctrl_bio_remin_POC_ballast_eco) then + !dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k) = MERGE( & + ! & ( par_bio_remin_kc(:,:)*dum_egbg_sfcpart(is_CaCO3,:,:,imld:n_k) + & + ! & par_bio_remin_ko(:,:)*dum_egbg_sfcpart(is_opal,:,:,imld:n_k) + & + ! & par_bio_remin_kl(:,:)*dum_egbg_sfcpart(is_det,:,:,imld:n_k) ) & + ! & /dum_egbg_sfcpart(is_POC,:,:,imld:n_k) , & + ! & 0.0, dum_egbg_sfcpart(is_POC,:,:,imld:n_k) > const_real_nullsmall) + dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k) = MERGE( & + & ( 0.085*dum_egbg_sfcpart(is_CaCO3,:,:,imld:n_k) + & + & 0.025*dum_egbg_sfcpart(is_opal,:,:,imld:n_k) + & + & 0.0*dum_egbg_sfcpart(is_det,:,:,imld:n_k) ) & + & /dum_egbg_sfcpart(is_POC,:,:,imld:n_k) , & + & 0.0, dum_egbg_sfcpart(is_POC,:,:,imld:n_k) > const_real_nullsmall) + dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k) = MERGE( & + & 1.0,dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k), dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k) > 1.0) + else + dum_egbg_sfcpart(is_POC_frac2,:,:,imld:n_k) = par_bio_remin_POC_frac2 + endif + dum_egbg_sfcpart(is_CaCO3_frac2,:,:,imld:n_k) = par_bio_remin_CaCO3_frac2 ! ---------------------------------------------------------- ! ! END ! ---------------------------------------------------------- ! diff --git a/genie-ecogem/src/fortran/ecogem_box.f90 b/genie-ecogem/src/fortran/ecogem_box.f90 index e8ff039a0..ea12cec49 100644 --- a/genie-ecogem/src/fortran/ecogem_box.f90 +++ b/genie-ecogem/src/fortran/ecogem_box.f90 @@ -35,7 +35,7 @@ SUBROUTINE quota_status( & ! DEFINE LOCAL VARIABLES ! ---------------------------------------------------------- ! integer :: io - ! + ! ! ***************************************************************** ! ******************** Evaluate Quota Status ********************** ! ***************************************************************** @@ -80,6 +80,7 @@ SUBROUTINE quota_limitation( & ! DEFINE LOCAL VARIABLES ! ---------------------------------------------------------- ! integer :: io + real,dimension(iomax,npmax) :: denom ! JDW Aaron Diatom 23 ! ! ***************************************************************** ! ******************** Evaluate Limitation *********************** @@ -100,21 +101,30 @@ SUBROUTINE quota_limitation( & VLlimit(:) = 0.0 ! (npmax) qreg(:,:) = 0.0 ! (iomax,npmax) qreg_h(:,:) = 0.0 ! (iomax,npmax) - + ! JDW: precalculate qmin-qmax to avoid divide by zero errorss + denom = merge(1.0/(qmax - qmin),0.0,qmax.gt.0.0) ! JDW: calculate 1.0/denominator and take care of instances of 1.0/0.0 Aaron Diatom 23 ! Calculate quota limitation terms ! N and Si take linear form - if (nquota) limit(iNitr,:) = (quota(iNitr,:) - qmin(iNitr,:)) / ( qmax(iNitr,:) - qmin(iNitr,:)) - if (squota) limit(iSili,:) = (quota(iSili,:) - qmin(iSili,:)) / ( qmax(iSili,:) - qmin(iSili,:)) + ! Modified to take into account no N limitation by diazotrophs - Fanny Jun20 + if (nquota) then + limit(iNitr,:) = (quota(iNitr,:) - qmin(iNitr,:)) * denom(iNitr,:) + limit(iNitr,:) = merge(1.0,limit(iNitr,:),pft.eq.'diazotroph') + endif + if (squota) limit(iSili,:) = (quota(iSili,:) - qmin(iSili,:)) * denom(iSili,:) ! JDW + !if (squota) limit(iSili,:) = (quota(iSili,:) - qmin(iSili,:)) / ( qmax(iSili,:) - qmin(iSili,:)) ! original Aaron Diatom 23 ! P and Fe take normalised Droop form if (pquota) limit(iPhos,:) = (1.0 - qmin(iPhos,:)/quota(iPhos,:)) / (1.0 - qmin(iPhos,:)/qmax(iPhos,:) ) if (fquota) limit(iIron,:) = (1.0 - qmin(iIron,:)/quota(iIron,:)) / (1.0 - qmin(iIron,:)/qmax(iIron,:) ) ! Set Von Leibig limitation according to most limiting nutrient (excluding iCarb=1) - VLlimit(:) = minval(limit(2:iomax,:),1) + ! VLlimit(:) = minval(limit(2:iomax,:),1) ! original + VLlimit(:) = minval(limit(2:max(iNitr,iPhos,iIron),:),1) ! JDW: calculate limitation for N,P,Fe only + VLlimit = merge(minval(limit(2:iomax,:),1),minval(limit(2:max(iNitr,iPhos,iIron),:),1),silicify.eq.1.0) ! JDW: in case of diatom reset taking into account SiO2 Aaron Diatom 23 do io = 2,iomax ! skip carbon index; quota = X:C biomass ratio ! Calculate linear regulation term - qreg(io,:) = (qmax(io,:) - quota(io,:)) / (qmax(io,:) - qmin(io,:) ) + qreg(io,:) = (qmax(io,:) - quota(io,:)) * denom(io,:) ! JDW + !qreg(io,:) = (qmax(io,:) - quota(io,:)) / (qmax(io,:) - qmin(io,:) ) ! original Aaron Diatom 23 ! Transform regulation term using hill number qreg_h(io,:) = qreg(io,:) ** hill enddo @@ -295,7 +305,9 @@ SUBROUTINE photosynthesis( & if (useNO3) VCN(:) = VCN(:) + up_inorg(iNO3,:) if (useNO2) VCN(:) = VCN(:) + up_inorg(iNO2,:) if (useNH4) VCN(:) = VCN(:) + up_inorg(iNH4,:) - elseif (pquota) then + ! To account for nitrogen fixation ! Fanny - June 2020 - Still need to check Moore et al (2002) + parameterise N:P_diazo (=40.0) - probably should scale with nitrogen fixation rate!! + VCN(:) = merge(up_inorg(iPO4,:) * 40.0,VCN(:),pft.eq.'diazotroph') ! Aaron Diatom 23 + elseif (pquota) then VCN(:) = up_inorg(iPO4,:) * 16.0 else print*,"!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!" diff --git a/genie-ecogem/src/fortran/ecogem_data.f90 b/genie-ecogem/src/fortran/ecogem_data.f90 index cc795b953..20a509a0e 100644 --- a/genie-ecogem/src/fortran/ecogem_data.f90 +++ b/genie-ecogem/src/fortran/ecogem_data.f90 @@ -156,6 +156,8 @@ SUBROUTINE sub_load_goin_ecogem() print*,'Corg 13C fractionation scheme ID string : ',trim(opt_d13C_DIC_Corg) print*,'b value for Popp et al. fractionation : ',par_d13C_DIC_Corg_b print*,'fractionation for intercellular C fixation : ',par_d13C_DIC_Corg_ef + ! ------------------- BALLAST PROPERTIES ------------------------------------------------------------------------------ ! + print*,'ballasting parameterization? : ',ctrl_bio_remin_POC_ballast_eco ! Aaron Diatom 23 ! --- RUN CONTROL --------------------------------------------------------------------------------------------------------- ! print*,'--- RUN CONTROL ------------------------------------' print*,'Continuing run? : ',ctrl_continuing @@ -170,8 +172,7 @@ SUBROUTINE sub_load_goin_ecogem() print*,'--- DATA SAVING: MISC ------------------------------' print*,'Restart in netCDF format? : ',ctrl_ncrst print*,'netCDF restart file name : ',trim(par_ncrst_name) - print*,'timeseries locations file name : ',trim(par_ecogem_timeseries_file) - end if ! end ctrl_debug_eco_init + end if ! end ctrl_debug_eco_init 66 format(a56,l2) 67 format(a56,i2) 71 format(a56,i4) @@ -334,12 +335,21 @@ SUBROUTINE sub_init_plankton() autotrophy(jp) = 1.0 heterotrophy(jp) = 0.0 elseif (pft(jp).eq.'synechococcus') then - NO3up(jp) = 0.0 - Nfix(jp) = 0.0 - calcify(jp) = 0.0 - silicify(jp) = 0.0 - autotrophy(jp) = 1.0 - heterotrophy(jp) = 0.0 + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 0.0 + silicify(jp) = 0.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= 1.0 + elseif (pft(jp).eq.'picoplankton') then + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 0.0 + silicify(jp) = 0.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= 1.0 elseif (pft(jp).eq.'picoeukaryote') then NO3up(jp) = 0.0 Nfix(jp) = 0.0 @@ -348,19 +358,21 @@ SUBROUTINE sub_init_plankton() autotrophy(jp) = 1.0 heterotrophy(jp) = 0.0 elseif (pft(jp).eq.'diatom') then - NO3up(jp) = 0.0 - Nfix(jp) = 0.0 - calcify(jp) = 0.0 - silicify(jp) = 0.0 - autotrophy(jp) = 1.0 - heterotrophy(jp) = 0.0 + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 0.0 + silicify(jp) = 1.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= par_diatom_palatability_mod ! JDW / Aaron Diatom 23 elseif (pft(jp).eq.'coccolithophore') then - NO3up(jp) = 0.0 - Nfix(jp) = 0.0 - calcify(jp) = 0.0 - silicify(jp) = 0.0 - autotrophy(jp) = 1.0 - heterotrophy(jp) = 0.0 + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 1.0 + silicify(jp) = 0.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= 1.0 * par_cocco_palatability_mod elseif (pft(jp).eq.'diazotroph') then NO3up(jp) = 0.0 Nfix(jp) = 0.0 @@ -369,12 +381,21 @@ SUBROUTINE sub_init_plankton() autotrophy(jp) = 1.0 heterotrophy(jp) = 0.0 elseif (pft(jp).eq.'phytoplankton') then - NO3up(jp) = 0.0 - Nfix(jp) = 0.0 - calcify(jp) = 0.0 - silicify(jp) = 0.0 - autotrophy(jp) = 1.0 - heterotrophy(jp) = 0.0 + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 0.0 + silicify(jp) = 0.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= 1.0 + elseif (pft(jp).eq.'eukaryote') then + NO3up(jp) = 1.0 + Nfix(jp) = 0.0 + calcify(jp) = 0.0 + silicify(jp) = 0.0 + autotrophy(jp) = 1.0 + heterotrophy(jp)= 0.0 + palatability(jp)= 1.0 ! Aaron Diatom 23 elseif (pft(jp).eq.'zooplankton') then NO3up(jp) = 0.0 Nfix(jp) = 0.0 @@ -390,18 +411,19 @@ SUBROUTINE sub_init_plankton() autotrophy(jp) = trophic_tradeoff heterotrophy(jp) = trophic_tradeoff elseif (pft(jp).eq.'foram') then - NO3up(jp) = 0.0 - Nfix(jp) = 0.0 - calcify(jp) = 0.0 - silicify(jp) = 0.0 - autotrophy(jp) = 0.0 - heterotrophy(jp) = 1.0 + NO3up(jp) = 0.0 + Nfix(jp) = 0.0 + calcify(jp) = 1.0 + silicify(jp) = 0.0 + autotrophy(jp) = trophic_tradeoff*0.5 + heterotrophy(jp)= trophic_tradeoff*0.5 + palatability(jp)= 0.5 else print*," " print*,"! ERROR !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!" print*,"! Unknown plankton functional type '"//trim(pft(jp))//"'" print*,"! Specified in input file "//TRIM(par_indir_name)//TRIM(par_ecogem_plankton_file) - print*,"Choose from Prochlorococcus, Synechococcus, Picoeukaryote, Diatom, Coccolithophore, Diazotroph, Phytoplankton, Zooplankton or Mixotroph" + print*,"Choose from Prochlorococcus, Synechococcus, Picoplankton, Picoeukaryote, Diatom, Coccolithophore, Diazotroph, Phytoplankton, Zooplankton or Mixotroph" print*,"!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!" stop endif @@ -442,6 +464,12 @@ SUBROUTINE sub_init_plankton() ! maximum photosynthetic rate ! vmax(iDIC,:) = vmaxDIC_a * volume(:) ** vmaxDIC_b * autotrophy(:) vmax(iDIC,:) = (vmaxDIC_a + log10(volume(:))) / (vmaxDIC_b + vmaxDIC_c * log10(volume(:)) + log10(volume(:))**2) * autotrophy(:) + ! modify rates for functional types + vmax(iDIC,:) = merge(vmaxDIC_a_pft_pico * volume(:) ** vmaxDIC_b_pft_pico,vmax(iDIC,:),pft.eq.'picoplankton') + vmax(iDIC,:) = merge(vmaxDIC_a_pft_cocco * volume(:) ** vmaxDIC_b_pft_cocco,vmax(iDIC,:),pft.eq.'coccolithophore') + vmax(iDIC,:) = merge(vmaxDIC_a_pft_diatom * volume(:) ** vmaxDIC_b_pft_diatom,vmax(iDIC,:),pft.eq.'diatom') + vmax(iDIC,:) = merge(vmaxDIC_a_pft_eukaryote * volume(:) ** vmaxDIC_b_pft_eukaryote,vmax(iDIC,:),pft.eq.'eukaryote') + vmax(iDIC,:) = merge(vmaxDIC_a_pft_diazotroph * volume(:) ** vmaxDIC_b_pft_diazotroph,vmax(iDIC,:),pft.eq.'diazotroph') ! Aaron Diatom 23 !----------------------------------------------------------------------------------------- if (nquota) then ! nitrogen parameters qmin(iNitr,:) = qminN_a * volume(:) ** qminN_b @@ -449,14 +477,14 @@ SUBROUTINE sub_init_plankton() if (maxval((qmin(iNitr,:)/qmax(iNitr,:))).gt.1.0) print*,"WARNING: Nitrogen Qmin > Qmax. Population inviable!" if (useNO3) then ! nitrate parameters vmax(iNO3,:) = vmaxNO3_a * volume(:) ** vmaxNO3_b * autotrophy(:) * NO3up(:) - affinity(iNO3,:) = affinNO3_a * volume(:) ** affinNO3_b * autotrophy(:) * NO3up(:) + affinity(iNO3,:) = affinNO3_a * volume(:) ** affinNO3_b * autotrophy(:) !* NO3up(:) Fanny - otherwise up_inorg(NO3) is NaN -> the best would be to prevent up_inorg to be Nan endif - if (useNO2) then ! nitrite parameters - vmax(iNO2,:) = vmaxNO2_a * volume(:) ** vmaxNO2_b * autotrophy(:) + if (useNO2) then ! nitrite parameters - modified to account for nitrogen fixation - Fanny Jun20 + vmax(iNO2,:) = vmaxNO2_a * volume(:) ** vmaxNO2_b * autotrophy(:) * (1.0 - Nfix(:)) affinity(iNO2,:) = affinNO2_a * volume(:) ** affinNO2_b * autotrophy(:) endif - if (useNH4) then ! ammonium parameters - vmax(iNH4,:) = vmaxNH4_a * volume(:) ** vmaxNH4_b * autotrophy(:) + if (useNH4) then ! ammonium parameters - modified to account for nitrogen fixation - Fanny Jun20 + vmax(iNH4,:) = vmaxNH4_a * volume(:) ** vmaxNH4_b * autotrophy(:) * (1.0 - Nfix(:)) affinity(iNH4,:) = affinNH4_a * volume(:) ** affinNH4_b * autotrophy(:) endif kexc(iNitr,:) = kexcN_a * volume(:) ** kexcN_b @@ -482,6 +510,13 @@ SUBROUTINE sub_init_plankton() vmax(iFe,:) = vmaxFe_a * volume(:) ** vmaxFe_b * autotrophy(:) affinity(iFe,:) = affinFe_a * volume(:) ** affinFe_b * autotrophy(:) kexc(iIron,:) = kexcFe_a * volume(:) ** kexcFe_b + ! Diazotrophs have higher Fe demands - Fanny Jun20 + qmin(iIron,:) = merge(qmin(iIron,:)*10.0,qmin(iIron,:),Nfix.eq.1.0) + qmax(iIron,:) = merge(qmax(iIron,:)*10.0,qmax(iIron,:),Nfix.eq.1.0) + affinity(iFe,:) = merge(affinity(iFe,:)/10.0,affinity(iFe,:),Nfix.eq.1.0) + !!! FANNY CHECK + !io = 1 + !write(*,*) 'qmin(iron)=',qmin(iIron,1:3), 'qmax(iron)=',qmax(iIron,1:3) endif !----------------------------------------------------------------------------------------- if (squota) then ! silicon parameters @@ -489,7 +524,7 @@ SUBROUTINE sub_init_plankton() qmax(iSili,:) = qmaxSi_a * volume(:) ** qmaxSi_b * silicify(:) if (maxval((qmin(iSili,:)/qmax(iSili,:))).gt.1.0) print*,"WARNING: Silicon Qmin > Qmax. Population inviable!" vmax(iSiO2,:) = vmaxSiO2_a * volume(:) ** vmaxSiO2_b * autotrophy(:) * silicify(:) - affinity(iSiO2,:) =affinSiO2_a * volume(:) ** affinSiO2_b * autotrophy(:) + affinity(iSiO2,:) = affinSiO2_a * volume(:) ** affinSiO2_b * autotrophy(:) kexc(iSili,:) = kexcSi_a * volume(:) ** kexcSi_b * silicify(:) endif !----------------------------------------------------------------------------------------- @@ -591,16 +626,16 @@ SUBROUTINE sub_init_plankton() close(302) ! grazing matrix - do jpred=1,npmax - if (heterotrophy(jpred).le.0.0) then - gkernel(jpred,:) = 0.0 - endif - do jprey=1,npmax-1 - WRITE(303,101,ADVANCE = "NO" ) gkernel(jpred,jprey) - enddo - WRITE(303,101,ADVANCE = "YES" ) gkernel(jpred,npmax) - enddo - close(303) + !do jpred=1,npmax + ! if (heterotrophy(jpred).le.0.0) then + ! gkernel(jpred,:) = 0.0 + ! endif + ! do jprey=1,npmax-1 + ! WRITE(303,101,ADVANCE = "NO" ) gkernel(jpred,jprey) + ! enddo + ! WRITE(303,101,ADVANCE = "YES" ) gkernel(jpred,npmax) + !enddo + !close(303) !**************************************************************************************** !**************************************************************************************** @@ -800,77 +835,7 @@ END SUBROUTINE sub_init_explicit_grazing_params ! ****************************************************************************************************************************** ! - ! LOAD TIME-SERIES LOCATIONS FROM INPUT FILE SUBROUTINE sub_init_timeseries() - SUBROUTINE sub_init_timeseries() - ! local variables - INTEGER::n - INTEGER :: loc_n_elements,loc_n_start - CHARACTER(len=16) :: loc_tser_name - REAL :: loc_tser_lat,loc_tser_lon - CHARACTER(len=255)::loc_filename - real,dimension(1:n_i)::loc_lon - real,dimension(1:n_j)::loc_lat - - ! get grid coordinates - loc_lon(1:n_i) = fun_get_grid_lon(n_i) - loc_lat(1:n_j) = fun_get_grid_lat(n_j) - - ! check file format and determine number of lines of data - loc_filename = TRIM(par_indir_name)//"/"//TRIM(par_ecogem_timeseries_file) - CALL sub_check_fileformat(loc_filename,loc_n_elements,loc_n_start) - - ! open file pipe - OPEN(unit=in,file=loc_filename,action='read') - ! goto start-of-file tag - DO n = 1,loc_n_start - READ(unit=in,fmt='(1X)') - END DO - - n_tser=loc_n_elements - - if (n_tser.gt.0) then - ALLOCATE(tser_name(n_tser),STAT=alloc_error) - call check_iostat(alloc_error,__LINE__,__FILE__) - ALLOCATE(tser_i(n_tser),STAT=alloc_error) - call check_iostat(alloc_error,__LINE__,__FILE__) - ALLOCATE(tser_j(n_tser),STAT=alloc_error) - call check_iostat(alloc_error,__LINE__,__FILE__) - - ! re-set filepipe - REWIND(unit=in) - ! goto start-of-file tag - DO n = 1,loc_n_start - READ(unit=in,fmt='(1X)') - END DO - - ! read in population specifications - if ((ctrl_debug_init > 0) .OR. ctrl_debug_eco_init) then - write(*,*) ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>' - print*,"Time-series output locations (shifted to sit of GEnIE grid)" - endif - DO n = 1,n_tser - READ(unit=in,FMT=*) & - & loc_tser_name, & ! COLUMN #02: time series name - & loc_tser_lat, & ! COLUMN #01: time series lat - & loc_tser_lon ! COLUMN #03: time series lon - tser_name(n) = TRIM(loc_tser_name) - if (loc_tser_lon.gt.maxval(loc_lon)) loc_tser_lon = loc_tser_lon - 360.00 - tser_i(n) = minloc(abs(loc_tser_lon-loc_lon), DIM=1) - tser_j(n) = minloc(abs(loc_tser_lat-loc_lat), DIM=1) - if ((ctrl_debug_init > 0) .OR. ctrl_debug_eco_init) then - print*,tser_name(n),loc_lat(tser_j(n)),loc_lon(tser_i(n)) - endif - END DO - if ((ctrl_debug_init > 0) .OR. ctrl_debug_eco_init) then - write(*,*) ' >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>' - endif - endif - ! close file pipe - CLOSE(unit=in) - END SUBROUTINE sub_init_timeseries - - - + ! ****************************************************************************************************************************** ! ! INITIALIZE INTEGRATED TIME-SLICE VALUE ARRAYS SUBROUTINE sub_init_int_timeslice() diff --git a/genie-ecogem/src/fortran/ecogem_lib.f90 b/genie-ecogem/src/fortran/ecogem_lib.f90 index 3161d9d67..f3cf92a68 100644 --- a/genie-ecogem/src/fortran/ecogem_lib.f90 +++ b/genie-ecogem/src/fortran/ecogem_lib.f90 @@ -108,9 +108,19 @@ MODULE ecogem_lib real :: biosynth ! cost of biosynthesis real :: k_w ! light attenuation by water real :: k_chl ! light attenuation by chlorophyll a + real :: vmaxDIC_a_pft_pico,vmaxDIC_b_pft_pico + real :: vmaxDIC_a_pft_cocco,vmaxDIC_b_pft_cocco + real :: vmaxDIC_a_pft_diatom,vmaxDIC_b_pft_diatom + real :: vmaxDIC_a_pft_eukaryote,vmaxDIC_b_pft_eukaryote + real :: vmaxDIC_a_pft_diazotroph,vmaxDIC_b_pft_diazotroph ! Aaron Diatom 23 namelist/ini_ecogem_nml/vmaxDIC_a,vmaxDIC_b,vmaxDIC_c namelist/ini_ecogem_nml/qcarbon_a,alphachl_a,PARfrac,chl2nmax,biosynth,k_w,k_chl namelist/ini_ecogem_nml/qcarbon_b,alphachl_b + namelist/ini_ecogem_nml/vmaxDIC_a_pft_pico,vmaxDIC_b_pft_pico + namelist/ini_ecogem_nml/vmaxDIC_a_pft_cocco,vmaxDIC_b_pft_cocco + namelist/ini_ecogem_nml/vmaxDIC_a_pft_diatom,vmaxDIC_b_pft_diatom + namelist/ini_ecogem_nml/vmaxDIC_a_pft_eukaryote,vmaxDIC_b_pft_eukaryote + namelist/ini_ecogem_nml/vmaxDIC_a_pft_diazotroph,vmaxDIC_b_pft_diazotroph ! Aaron Diatom 23 logical::ctrl_restrict_mld ! restrict MLD NAMELIST /ini_ecogem_nml/ctrl_restrict_mld logical::ctrl_PARseaicelimit ! PAR attenutation by sea-ice cover? @@ -161,8 +171,6 @@ MODULE ecogem_lib NAMELIST /ini_ecogem_nml/nsubtime! CHARACTER(len=127)::par_ecogem_plankton_file NAMELIST /ini_ecogem_nml/par_ecogem_plankton_file - CHARACTER(len=127)::par_ecogem_timeseries_file - NAMELIST /ini_ecogem_nml/par_ecogem_timeseries_file ! JDW force T fields logical::ctrl_force_T namelist /ini_ecogem_nml/ctrl_force_T @@ -182,6 +190,12 @@ MODULE ecogem_lib NAMELIST /ini_ecogem_nml/par_d13C_DIC_Corg_b real::par_d13C_DIC_Corg_ef ! frac for intercellular C fix NAMELIST /ini_ecogem_nml/par_d13C_DIC_Corg_ef + ! ------------------- EXPORT PROPERTIES ---------------------------------------------------------------------------------------- ! + LOGICAL::ctrl_bio_remin_POC_ballast_eco ! ballasting parameterization? + NAMELIST /ini_ecogem_nml/ctrl_bio_remin_POC_ballast_eco + !REAL,DIMENSION(n_i,n_j)::par_bio_remin_kc ! + !REAL,DIMENSION(n_i,n_j)::par_bio_remin_ko ! + !REAL,DIMENSION(n_i,n_j)::par_bio_remin_kl ! ------------------- RUN CONTROL ---------------------------------------------------------------------------------------------- ! logical::ctrl_continuing ! continuing run? NAMELIST /ini_ecogem_nml/ctrl_continuing @@ -216,6 +230,11 @@ MODULE ecogem_lib ! ------------------- MISC ----------------------------------------------------------------------------------------------------- ! logical::ctrl_limit_neg_biomass NAMELIST /ini_ecogem_nml/ctrl_limit_neg_biomass + ! functional type parameters + real::par_cocco_palatability_mod , par_cocco_vmax_mod + namelist /ini_ecogem_nml/ par_cocco_palatability_mod,par_cocco_vmax_mod + real::par_diatom_palatability_mod , par_diatom_vmax_mod + namelist /ini_ecogem_nml/ par_diatom_palatability_mod,par_diatom_vmax_mod ! Aaron Diatom 23 real::par_beta_POCtoDOC namelist/ini_ecogem_nml/par_beta_POCtoDOC logical::ctrl_Tdep_POCtoDOC diff --git a/genie-ecogem/src/fortran/initialise_ecogem.f90 b/genie-ecogem/src/fortran/initialise_ecogem.f90 index 35d6eed24..4c6cf95cd 100644 --- a/genie-ecogem/src/fortran/initialise_ecogem.f90 +++ b/genie-ecogem/src/fortran/initialise_ecogem.f90 @@ -28,6 +28,7 @@ SUBROUTINE initialise_ecogem( & integer,DIMENSION(n_i,n_j),INTENT(in)::dum_k1 ! REAL,DIMENSION(n_k),INTENT(in)::dum_dz,dum_dza ! REAL,DIMENSION(0:n_j),INTENT(in)::dum_sv ! + integer :: stat CHARACTER(len=64)::site_string ! ---------------------------------------------------------- ! ! local variables @@ -70,9 +71,7 @@ SUBROUTINE initialise_ecogem( & ! get specifications of plankton populations from input file CALL sub_init_populations() - ! get names and locations of time-series sites for output - CALL sub_init_timeseries() - + if (ctrl_debug_eco_init) then write(*,*) ' ---------------------------------------------------' write(*,*) '- Plankton population specifications from input file' @@ -330,8 +329,8 @@ SUBROUTINE initialise_ecogem( & ! ---------------------------------------------------------- ! open(301,File=TRIM(par_outdir_name)//"/Plankton_params.txt" ,Status="Replace",Action="Write") open(302,File=TRIM(par_outdir_name)//"/Plankton_params_nohead.dat",Status="Replace",Action="Write") - open(303,File=TRIM(par_outdir_name)//"/Plankton_grazing.dat" ,Status="Replace",Action="Write") - +! open(303,File=TRIM(par_outdir_name)//"/Plankton_grazing.dat" ,Status="Replace",Action="Write") + open(304,File=TRIM(par_outdir_name)//"/Ecogem_properties.dat" ,Status="Replace",Action="Write") ! make wet mask for ocean cells wet_mask_ij(:,:) = MERGE(1,0,goldstein_k1.le.n_k) do k=1,n_k diff --git a/genie-main/configs/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config b/genie-main/configs/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config new file mode 100644 index 000000000..607c4cc6e --- /dev/null +++ b/genie-main/configs/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config @@ -0,0 +1,173 @@ +# ******************************************************************* +# CONFIGURATION TEMPLATE (EMBM + GOLDSTEIN + GOLDSTEIN SEA-ICE + ATCHEM + BIOGEM + ECOGEM) +# ******************************************************************* + +# ******************************************************************* +# GENIE COMPONENT SELECTION +# ******************************************************************* +# make .TRUE. the cGENIE modules to be included +# ******************************************************************* +ma_flag_ebatmos=.TRUE. +ma_flag_goldsteinocean=.TRUE. +ma_flag_goldsteinseaice=.TRUE. +ma_flag_biogem=.TRUE. +ma_flag_atchem=.TRUE. +ma_flag_sedgem=.FALSE. +ma_flag_rokgem=.FALSE. +ma_flag_gemlite=.FALSE. +ma_flag_ecogem=.TRUE. +# ******************************************************************* + +# ******************************************************************* +# GRID & BOUNDARY CONDITION CONFIGURATION +# ******************************************************************* +# insert the automatically generated muffingen parameter list here +# ******************************************************************* +# Topography +ma_fname_topo='worjh2' +# Grid resolution of climate components +GENIENXOPTS='-DGENIENX=36' +GENIENYOPTS='-DGENIENY=36' +GENIENLOPTS='-DGENIENL=1' +GENIENXOPTS='$(DEFINE)GENIENX=36' +GENIENYOPTS='$(DEFINE)GENIENY=36' +GOLDSTEINNLONSOPTS='$(DEFINE)GOLDSTEINNLONS=36' +GOLDSTEINNLATSOPTS='$(DEFINE)GOLDSTEINNLATS=36' +GOLDSTEINNLEVSOPTS='$(DEFINE)GOLDSTEINNLEVS=16' +# Topography for climate components +ea_topo=worjh2 +go_topo=worjh2 +gs_topo=worjh2 +# ******************************************************************* + +# ******************************************************************* +# TRACER CONFIGURATION +# ******************************************************************* +# the total number of tracers includes T and S +# T and S do not need to be explicited selected and initialzied +# ******************************************************************* +# Set number of tracers +GOLDSTEINNTRACSOPTS='$(DEFINE)GOLDSTEINNTRACS=19' +# list selected biogeochemical tracers +gm_atm_select_3=.true. # pCO2 -- 'carbon dioxide (CO2)' +gm_atm_select_4=.true. # pCO2_13C -- 'd13C CO2' +gm_atm_select_6=.true. # pO2 -- 'oxygen (O2)' +gm_atm_select_16=.true. # pH2S -- 'hydrogen sulphide (H2S)' +gm_ocn_select_3=.true. # DIC -- 'dissolved inorganic carbon (DIC)' +gm_ocn_select_4=.true. # DIC_13C -- 'd13C of DIC' +gm_ocn_select_8=.true. # PO4 -- 'dissolved phosphate (PO4)' +gm_ocn_select_10=.true. # O2 -- 'dissolved oxygen (O2)' +gm_ocn_select_12=.true. # ALK -- 'alkalinity (ALK)' +gm_ocn_select_13=.true. # SiO2 -- 'aqueous silicic acid (H4SiO4)' +gm_ocn_select_14=.true. # SiO2_30Si -- 'd30Si of H4SiO4' +gm_ocn_select_15=.true. # DOM_C -- 'dissolved organic matter (DOM); carbon' +gm_ocn_select_16=.true. # DOM_C_13C -- 'd13C of DOM-C' +gm_ocn_select_20=.true. # DOM_P -- 'dissolved organic matter; phosphorous' +gm_ocn_select_22=.true. # DOM_Fe -- 'dissolved organic matter; iron' +gm_ocn_select_90=.true. # TDFe -- 'total dissolved Fe' +gm_ocn_select_42=.true. # TL -- 'total dissolved ligand' +gm_ocn_select_35=.true. # Ca -- 'dissolved calcium (Ca)' +gm_ocn_select_38=.true. # SO4 -- 'dissolved sulphate (SO4)' +gm_ocn_select_40=.true. # H2S -- 'dissolved hydrogen sulphide (H2S)' +gm_ocn_select_50=.true. # Mg -- 'dissolved Magnesium (Mg)' +gm_sed_select_3=.true. # POC -- 'particulate organic carbon (POC)' +gm_sed_select_4=.true. # POC_13C -- 'd13C of POC' +gm_sed_select_8=.true. # POP -- 'particulate organic phosphate (POP)' +gm_sed_select_10=.true. # POFe -- 'particulate organic iron (POFe)' +gm_sed_select_13=.true. # POM_Fe -- 'POM scavenged Fe' +gm_sed_select_14=.true. # CaCO3 -- 'calcium carbonate (CaCO3)' +gm_sed_select_15=.true. # CaCO3_13C -- 'd13C of CaCO3' +gm_sed_select_21=.true. # CaCO3_Fe -- 'CaCO3 scavenged Fe' +gm_sed_select_22=.true. # det -- 'detrital (refractory) material' +gm_sed_select_25=.true. # det_Fe -- 'detrital scavenged Fe' +gm_sed_select_26=.true. # opal -- 'opal' +gm_sed_select_27=.true. # opal_30Si -- 'd30Si of opal' +gm_sed_select_32=.true. # ash -- 'ash' +gm_sed_select_33=.true. # POC_frac2 - 'n/a' +gm_sed_select_34=.true. # CaCO3_frac2 -- 'n/a' +gm_sed_select_35=.true. # opal_frac2 -- 'n/a' +gm_sed_select_36=.true. # CaCO3_age -- 'CaCO3 numerical age tracer' +##gm_ocn_select_66=.true. # Csoft +# list biogeochemical tracer initial values +ac_atm_init_3=278.0E-06 +ac_atm_init_4=-6.5 +ac_atm_init_6=0.2095 +bg_ocn_init_3=2.244E-03 +bg_ocn_init_4=0.4 +bg_ocn_init_8=2.159E-06 +bg_ocn_init_10=1.696E-04 +bg_ocn_init_12=2.363E-03 +bg_ocn_init_13=85.0E-06 +bg_ocn_init_14=1.1 +bg_ocn_init_90=0.650E-09 +bg_ocn_init_42=1.000E-09 +bg_ocn_init_35=1.025E-02 +bg_ocn_init_38=2.916E-02 +bg_ocn_init_50=5.282E-02 +# ******************************************************************* + +# ******************************************************************* +# PHYSICAL CLIMATE CALIBRATION +# ******************************************************************* +# based on Cao et al. [2009] with the following exceptions: +# (1) warmer (5C) ocean start (could be 10C for a more intense greenhouse world) +# (2) scaling of the freshwater re-balancing flux to zero +# (3) application of a reduced sea-ice diffusivity and +# prescribed maximum fractional area for sea-ice advection +# (4) recommended: turn off isoneutral isopycnal/diapycnal mixing scheme +# (5) NOTE: no reduced diffusivity over Antarctica +# ******************************************************************* +# rel +go_12=0.9000000 +# scl_tau / SclTau +go_13=1.531013488769531300 +# ocean diffusivites iso (or horiz) / OcnHorizDiff +go_14=1494.438354492187500000 +# ocean diffusivites dia (or vert) / OcnVertDiff +go_15=0.000025363247914356 +# inverse minimum drag in days / InvDrag +go_16=2.710164785385131800 +# scl_tau (should be same as GOLDSTEIN's value) / SclTau +ea_11=1.531013488769531300 +# atm. diff. amp. for T / AtmDiffAmpT +ea_12=5204945.000000000000000000 +# atm. diff. amp. for q / AtmDiffAmpQ +ea_13=1173269.250000000000000000 +# dist'n width / AtmDiffWidthT +ea_14=1.410347938537597700 +# dist'n slope / AtmDiffSlopeT +ea_15=0.090003050863742828 +# atm. advection factor for T_z / AtmAdvectCoeffTm +ea_16=0.001037851092405617 +# atm. advection factor for T_m / AtmAdvectCoeffQm +ea_17=0.0000000E+00 +# atm. advection factor for q_z / AtmAdvectCoeffQz +ea_18=0.164652019739151000 +# atm. advection factor for q_m / AtmAdvectCoeffQz +ea_19=0.164652019739151000 +# temp0 -- start with a warm ocean +go_10=5.0 +# temp1 -- start with a warm ocean +go_11=5.0 +# SclFWF +ea_28=0.726862013339996340 +# sea-ice eddy diffusivity / SeaiceDiff +gs_11=3573.718017578125000000 +#diffusivity scaling factor +ea_diffa_scl=0.25 +#grid point distance over which scalar is applied (j direction) +ea_diffa_len=3 +# set seasonal cycle +ea_dosc=.true. +go_dosc=.true. +gs_dosc=.true. +# isoneutral isopycnal/diapycnal mixing scheme +# it is recommended that it is turned OFF (=.false.) for 'fake' worlds +go_diso=.true. +# ******************************************************************* + +# ******************************************************************* +# USER-APPENDED OPTIONS FOLLOW ... +# ******************************************************************* +# (the following parameter text is appended automatically) +# ******************************************************************* diff --git a/genie-main/src/xml-config/xml/definition.xml b/genie-main/src/xml-config/xml/definition.xml index bb86c0f99..fda826fe7 100644 --- a/genie-main/src/xml-config/xml/definition.xml +++ b/genie-main/src/xml-config/xml/definition.xml @@ -8852,7 +8852,7 @@ par_bio_red_PC_alpha2 scales the offset of 6.0e-3 of Galbraith & Martiny, 2015 C - 0.0 + 0.002 Silicon minimum quota - intercept @@ -8860,7 +8860,7 @@ par_bio_red_PC_alpha2 scales the offset of 6.0e-3 of Galbraith & Martiny, 2015 C Silicon minimum quota - exponent - 0.0 + 0.004 Silicon maximum quota - intercept @@ -8868,19 +8868,19 @@ par_bio_red_PC_alpha2 scales the offset of 6.0e-3 of Galbraith & Martiny, 2015 C Silicon maximum quota - exponent - 0.0 + 0.077 Maximum silica uptake rate - intercept - 0.0 + -0.27 Maximum silica uptake rate - exponent - 0.0 + 3.208 Silica uptake affinity (Michaelis-Menten) - intercept - 0.0 + -0.54 Silica uptake affinity (Michaelis-Menten) - exponent @@ -8904,6 +8904,46 @@ par_bio_red_PC_alpha2 scales the offset of 6.0e-3 of Galbraith & Martiny, 2015 C -3.80 maximum photosynthetic rate - c + + 0.9 + maximum photosynthetic rate - a + + + 0.08 + maximum photosynthetic rate - a + + + 1.4 + maximum photosynthetic rate - a + + + -0.08 + maximum photosynthetic rate - a + + + 3.9 + maximum photosynthetic rate - a + + + -0.08 + maximum photosynthetic rate - a + + + 1.7 + maximum photosynthetic rate - a + + + -0.08 + maximum photosynthetic rate - a + + + 0.95 + Diazotroph maximum photosynthetic rate (d-1) - intercept + + + -0.08 + Diazotroph maximum photosynthetic rate - exponent + ! Aaron Diatom 23 1.45e-11 Carbon per cell - intercept @@ -9175,10 +9215,23 @@ par_bio_red_PC_alpha2 scales the offset of 6.0e-3 of Galbraith & Martiny, 2015 C temperature.dat Input file for forcing temperature in ecogem - - timeseries_sites.eco - timeseries locations file name + + + 1.0 + modifier for coccolithophore palatability + + + 1.0 + modifier for coccolithophore uptake rate + + 1.0 + Modifier for diatom palatability + + + 1.0 + Modifier for diatom uptake and growth ! Aaron Diatom 23 + diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco new file mode 100644 index 000000000..2231035f5 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco @@ -0,0 +1,45 @@ + + 01 02 03 + \/ \/ \/ + +-START-OF-DATA- + Diatom 2.00 1 + Diatom 20.00 1 + Diatom 200.00 1 + Picoplankton 0.6 1 + Picoplankton 2.00 1 + Eukaryote 20.00 1 + Eukaryote 200.00 1 + Zooplankton 6.00 1 + Zooplankton 20.00 1 + Zooplankton 200.00 1 + Zooplankton 2000.00 1 +-END-OF-DATA- + + /\ /\ /\ + 01 02 03 + +DATA FORMAT AND ORDER +--------------------- + +COLUMN #01: plankton functional type name +COLUMN #02: plankton diameter (micrometers) +COLUMN #03: number of randomised replicates + +INFO: TRACER ASSIGNMENT RULES +----------------------------- +Plankton functional type one of: Prochlorococcus + Synechococcus + Picoeukaryote + Picoplankton + Diatom + Coccolithophore + Diazotroph + Eukaryote + Phytoplankton + Zooplankton + Mixotroph + + + + diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 new file mode 100644 index 000000000..8031867b1 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 @@ -0,0 +1,212 @@ +# ******************************************************************* +# *** Like muffin.CBE.worjh2.BASESFeTDTL.Albani with Si cycle on ********************** +# ******************************************************************* +# +# *** CLIMATE ******************************************************* +# +# set climate feedback (climate responding to changing pCO2) +ea_36=y +# +# *** BIOLOGICAL NEW PRODUCTION ************************************* +# +# biological scheme ID string +# NOTE: with ECOGEM, no BIOGEM biological scheme must be selected +bg_par_bio_prodopt="NONE" +# +# *** ORGANIC MATTER EXPORT RATIOS ********************************** +# +# [dealt with by ECOGEM] +# +# *** INORGANIC MATTER EXPORT RATIOS ******************************** +# +# [dealt with by ECOGEM] +# +# *** REMINERALIZATION ********************************************** +# +# DOC lifetime (yrs) +bg_par_bio_remin_DOMlifetime=0.5 +# initial fractional abundance of POC component #2 +bg_par_bio_remin_POC_frac2=0.0557 +# depth of remineralization or particulate organic matter +bg_par_bio_remin_POC_eL1=589.9451 +# remineralization length #2 for POC +bg_par_bio_remin_POC_eL2=1000000.0 +# initial fractional abundance of CaCO3 component #2 +bg_par_bio_remin_CaCO3_frac2=0.45 +# depth of remineralization or CaCO3 +bg_par_bio_remin_CaCO3_eL1=1.8905e+003 +# remineralization length #2 for CaCO3 +bg_par_bio_remin_CaCO3_eL2=1000000.0 +# *** optional changes to align with PALEO recommendations ********** +# set 'instantaneous' water column remineralziation +bg_par_bio_remin_sinkingrate_physical=9.9E9 +bg_par_bio_remin_sinkingrate_reaction=125.0 +# +# --- NITROGEN ------------------------------------------------------ Fanny - June 2020 +## Nitrification +# NH4 oxidation rate constant (yr-1) +bg_par_nitri_mu=7.30 +# NH4 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_NH4=0.01E-06 +# O2 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_O2=0.02E-06 +## Denitrification +#F switch hard threshold scheme for OM remineralisation +bg_ctrl_bio_remin_thresh = .true. +#F denitrification O2 threshold (40E-6, Naafs etal 2019) +bg_par_bio_remin_cthresh_O2=30E-6 +# +# iron tracer scheme +# NOTE: the base-config requires TFe and TL tracers +bg_opt_geochem_Fe='hybrid' +# exponent for aeolian Fe solubility [use 1.0 for uniform solubility] +bg_par_det_Fe_sol_exp=0.500 +# aeolian Fe solubility +bg_par_det_Fe_sol=0.002441 +# modifier of the scavenging rate of dissolved Fe +bg_par_scav_Fe_sf_POC=0.225 +# no scavenged regeneration +bg_par_scav_fremin=0.0 +# return POFe +bg_ctrl_bio_NO_fsedFe=.false. +# Variable Fe:C +bg_ctrl_bio_red_fixedFetoC=.false. +# adjust pK'(FeL) +bg_par_K_FeL_pP=11.0 +#(max) C/Fe organic matter ratio +bg_par_bio_red_POFe_POC=250000.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- power +bg_par_bio_FetoC_pP=-0.4225 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- scaling +bg_par_bio_FetoC_K=103684.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- constant +bg_par_bio_FetoC_C=0.0 +# +# --- Si ---------------------------------------------- +# +# Si:C [DEFAULT: 0.175] ***** TO CHECK +bg_par_bio_red_POC_opal=0.65 +# remin ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=125.0 +# 30Si ***** TO CHECK +# epsilon 30Si associated with opal formation [DEFAULT: -1.1] +bg_par_d30Si_opal_epsilon=-1.1 +# +# *** ECOGEM ******************************************************** +# +# ecosystem configuration +# PFTs with diatoms, pico and eukaryotes Fanny - Jun20 +eg_par_ecogem_plankton_file ='3Diat_4ZP_PiEu.eco' + +#################### Nitrogen ############################ +eg_useNO3 =.false. +eg_nquota =.false. +################## Phosphorus ############################ +eg_usePO4 =.true. +eg_pquota =.true. +######################## Iron ############################ +eg_useFe =.true. +eg_fquota =.true. +################# Chlorophyll ############################ +eg_chlquota =.true. +################# d13C ################################### +eg_useDIC_13C =.true. +#################### Silicate ############################ +eg_useSiO2 =.true. +eg_squota =.true. + +# Tuned - Ward et al. (2018) +eg_qminP_a = 3.33e-3 +eg_qminFe_a = 1.00e-6 +eg_qmaxFe_a = 4.00e-6 +# Si properties - Fanny June2020 +eg_vmaxSiO2_a=4.4e-2 +eg_vmaxSiO2_b=0.06 +eg_qminSi_a=0.033600 +eg_qmaxSi_a=0.176000 +eg_affinSiO2_a = 3.900 +eg_affinSiO2_b = -0.35 + +# eukaryote photosynthetic rate - Fanny Jun20 (equivalent to 0.56 times diatoms Pmax) +eg_vmaxDIC_a_pft_eukaryote = 2.2000 + +# ??? +eg_ns=2 +# ??? +eg_respir_a=0 +# DOM parameters +eg_beta_mort_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_mort_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_mort_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +eg_beta_graz_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_graz_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_graz_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +# ??? +eg_nsubtime=25 +eg_n_keco=1 +# exponent for modifier of CaCO3:POC export ratio +eg_par_bio_red_POC_CaCO3_pP = 0.7440 # exponent for modifier of CaCO3:POC export ratio +# underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +eg_par_bio_red_POC_CaCO3 = 0.0285 # underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +# +# *** DATA SAVING *************************************************** +# +# BASIC + biology + tracer + proxy diagnostics +bg_par_data_save_level=10 +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst = .false. +eg_ctrl_continuing = .false. +# +# *** FORCINGS ****************************************************** +# +bg_par_forcing_name="worjh2.RpCO2_Rp13CO2.Albani.0ka" +bg_par_atm_force_scale_val_3=278.0E-06 +bg_par_atm_force_scale_val_4=-6.5 +# +# *** MISC ********************************************************** +# +# kraus-turner mixed layer scheme on (1) or off (0) +go_imld = 1 +# *** optional changes to align with PALEO recommendations ********** +# set mixed layer to be only diagnosed (for ECOGEM) +go_ctrl_diagmld=.true. +# add seaice attenuation of PAR +eg_ctrl_PARseaicelimit=.true. +# relative partitioning of C into DOM +#eg_par_beta_POCtoDOC=0.75 +# maximum time-scale to geochemical reaction completion (days) +bg_par_bio_geochem_tau=90.0 +# extend solubility and geochem constant T range (leave S range as default) +gm_par_geochem_Tmin = -2.0 +gm_par_geochem_Tmax = 45.0 +gm_par_carbchem_Tmin = -2.0 +gm_par_carbchem_Tmax = 45.0 +# +# ******************************************************************* +# *** END *********************************************************** +# ******************************************************************* +# +Ensemble created: 180712 ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=83.146 +bg_par_bio_red_POC_opal=0.17185 +Ensemble created: 221224 +eg_qminP_a=0.0027022 +eg_qmaxP_a=0.0216773 +eg_qminFe_a=6.8572e-07 +eg_qmaxFe_a=4.09512e-06 +eg_qminSi_a=0.043259 +eg_qmaxSi_a=0.407638 +eg_affinSiO2_a=4.7769 +eg_affinSiO2_b=-0.40131 +eg_affinPO4_a=0.94403 +eg_affinPO4_b=-0.43718 +eg_affinFe_a=0.17761 +eg_affinFe_b=-0.2574 +eg_vmaxFe_a=0.00016885 +eg_vmaxFe_b=-0.12635 +eg_vmaxSiO2_a=0.068039 +eg_vmaxSiO2_b=0.031868 +eg_par_diatom_palatability_mod=0.92802 +bg_par_bio_remin_sinkingrate_reaction=49.689 diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys new file mode 100644 index 000000000..9ad35c90f --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys @@ -0,0 +1,184 @@ +# ******************************************************************* +# *** Like muffin.CBE.worjh2.BASESFeTDTL.Albani with Si cycle on ********************** +# ******************************************************************* +# +# *** CLIMATE ******************************************************* +# +# set climate feedback (climate responding to changing pCO2) +ea_36=y +# +# *** BIOLOGICAL NEW PRODUCTION ************************************* +# +# # +# *** ORGANIC MATTER EXPORT RATIOS ********************************** +# +# +# +# *** INORGANIC MATTER EXPORT RATIOS ******************************** +# +# underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +bg_par_bio_red_POC_CaCO3=0.0485 +# exponent for modifier of CaCO3:POC export ratio +bg_par_bio_red_POC_CaCO3_pP=0.7440 + +# +# *** REMINERALIZATION ********************************************** +# +# DOC lifetime (yrs) +bg_par_bio_remin_DOMlifetime=0.5 +# initial fractional abundance of POC component #2 +bg_par_bio_remin_POC_frac2=0.0557 +# depth of remineralization or particulate organic matter +bg_par_bio_remin_POC_eL1=589.9451 +# remineralization length #2 for POC +bg_par_bio_remin_POC_eL2=1000000.0 +# initial fractional abundance of CaCO3 component #2 +bg_par_bio_remin_CaCO3_frac2=0.45 +# depth of remineralization or CaCO3 +bg_par_bio_remin_CaCO3_eL1=1.8905e+003 +# remineralization length #2 for CaCO3 +bg_par_bio_remin_CaCO3_eL2=1000000.0 +# *** optional changes to align with PALEO recommendations ********** +# set 'instantaneous' water column remineralziation +bg_par_bio_remin_sinkingrate_physical=9.9E9 +bg_par_bio_remin_sinkingrate_reaction=125.0 +# +# --- NITROGEN ------------------------------------------------------ Fanny - June 2020 +## Nitrification +# NH4 oxidation rate constant (yr-1) +bg_par_nitri_mu=7.30 +# NH4 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_NH4=0.01E-06 +# O2 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_O2=0.02E-06 +## Denitrification +#F switch hard threshold scheme for OM remineralisation +bg_ctrl_bio_remin_thresh = .true. +#F denitrification O2 threshold (40E-6, Naafs etal 2019) +bg_par_bio_remin_cthresh_O2=30E-6 +# +# iron tracer scheme +# NOTE: the base-config requires TFe and TL tracers +bg_opt_geochem_Fe='hybrid' +# exponent for aeolian Fe solubility [use 1.0 for uniform solubility] +bg_par_det_Fe_sol_exp=0.500 +# aeolian Fe solubility +bg_par_det_Fe_sol=0.002441 +# modifier of the scavenging rate of dissolved Fe +bg_par_scav_Fe_sf_POC=0.225 +# no scavenged regeneration +bg_par_scav_fremin=0.0 +# return POFe +bg_ctrl_bio_NO_fsedFe=.false. +# Variable Fe:C +bg_ctrl_bio_red_fixedFetoC=.false. +# adjust pK'(FeL) +bg_par_K_FeL_pP=11.0 +#(max) C/Fe organic matter ratio +bg_par_bio_red_POFe_POC=250000.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- power +bg_par_bio_FetoC_pP=-0.4225 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- scaling +bg_par_bio_FetoC_K=103684.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- constant +bg_par_bio_FetoC_C=0.0 +# +# --- Si ---------------------------------------------- +# +# Si:C [DEFAULT: 0.175] ***** TO CHECK +bg_par_bio_red_POC_opal=0.65 +# remin ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=125.0 +# 30Si ***** TO CHECK +# epsilon 30Si associated with opal formation [DEFAULT: -1.1] +bg_par_d30Si_opal_epsilon=-1.1 +# +# *** ECOGEM ******************************************************** +# +gm_ctrl_debug_init =0 +eg_ctrl_debug_eco_init =.false. + +eg_par_ecogem_plankton_file ='8P8Z.eco' + +#################### Nitrogen ############################ +eg_useNO3 =.false. +eg_nquota =.false. +################## Phosphorus ############################ +eg_usePO4 =.true. +eg_pquota =.true. +######################## Iron ############################ +eg_useFe =.true. +eg_fquota =.true. +################# Chlorophyll ############################ +eg_chlquota =.true. +################# d13C ################################### +eg_useDIC_13C =.true. + +# Tuned +eg_qminP_a = 3.33e-3 +eg_qminFe_a = 1.00e-6 +eg_qmaxFe_a = 4.00e-6 + +eg_ns = 2 + +eg_respir_a = 0 + +eg_beta_mort_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_mort_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_mort_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +eg_beta_graz_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_graz_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_graz_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) + +eg_par_bio_red_POC_CaCO3 = 0.0285 # underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +eg_par_bio_red_POC_CaCO3_pP = 0.7440 # exponent for modifier of CaCO3:POC export ratio + +eg_nsubtime =25 +eg_n_keco =1 + +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst =.false. +eg_ctrl_continuing =.false. + +# *** DATA SAVING *************************************************** +# +# BASIC + biology + tracer + proxy diagnostics +bg_par_data_save_level=10 +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst = .false. +eg_ctrl_continuing = .false. +# +# *** FORCINGS ****************************************************** +# +bg_par_forcing_name="worjh2.RpCO2_Rp13CO2.Albani.0ka" +bg_par_atm_force_scale_val_3=278.0E-06 +bg_par_atm_force_scale_val_4=-6.5 +# +# *** MISC ********************************************************** +# +# kraus-turner mixed layer scheme on (1) or off (0) +go_imld = 1 +# *** optional changes to align with PALEO recommendations ********** +# set mixed layer to be only diagnosed (for ECOGEM) +go_ctrl_diagmld=.true. +# add seaice attenuation of PAR +eg_ctrl_PARseaicelimit=.true. +# relative partitioning of C into DOM +#eg_par_beta_POCtoDOC=0.75 +# maximum time-scale to geochemical reaction completion (days) +bg_par_bio_geochem_tau=90.0 +# extend solubility and geochem constant T range (leave S range as default) +gm_par_geochem_Tmin = -2.0 +gm_par_geochem_Tmax = 45.0 +gm_par_carbchem_Tmin = -2.0 +gm_par_carbchem_Tmax = 45.0 +# +# ******************************************************************* +# *** END *********************************************************** +# ******************************************************************* +# +Ensemble created: 180712 ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=83.146 +bg_par_bio_red_POC_opal=0.17185 diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys_eco b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys_eco new file mode 100644 index 000000000..0a8689ff4 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1_phys_eco @@ -0,0 +1,212 @@ +# ******************************************************************* +# *** Like muffin.CBE.worjh2.BASESFeTDTL.Albani with Si cycle on ********************** +# ******************************************************************* +# +# *** CLIMATE ******************************************************* +# +# set climate feedback (climate responding to changing pCO2) +ea_36=y +# +# *** BIOLOGICAL NEW PRODUCTION ************************************* +# +# biological scheme ID string +# NOTE: with ECOGEM, no BIOGEM biological scheme must be selected +bg_par_bio_prodopt="NONE" +# +# *** ORGANIC MATTER EXPORT RATIOS ********************************** +# +# [dealt with by ECOGEM] +# +# *** INORGANIC MATTER EXPORT RATIOS ******************************** +# +# [dealt with by ECOGEM] +# +# *** REMINERALIZATION ********************************************** +# +# DOC lifetime (yrs) +bg_par_bio_remin_DOMlifetime=0.5 +# initial fractional abundance of POC component #2 +bg_par_bio_remin_POC_frac2=0.0557 +# depth of remineralization or particulate organic matter +bg_par_bio_remin_POC_eL1=589.9451 +# remineralization length #2 for POC +bg_par_bio_remin_POC_eL2=1000000.0 +# initial fractional abundance of CaCO3 component #2 +bg_par_bio_remin_CaCO3_frac2=0.45 +# depth of remineralization or CaCO3 +bg_par_bio_remin_CaCO3_eL1=1.8905e+003 +# remineralization length #2 for CaCO3 +bg_par_bio_remin_CaCO3_eL2=1000000.0 +# *** optional changes to align with PALEO recommendations ********** +# set 'instantaneous' water column remineralziation +bg_par_bio_remin_sinkingrate_physical=9.9E9 +bg_par_bio_remin_sinkingrate_reaction=125.0 +# +# --- NITROGEN ------------------------------------------------------ Fanny - June 2020 +## Nitrification +# NH4 oxidation rate constant (yr-1) +bg_par_nitri_mu=7.30 +# NH4 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_NH4=0.01E-06 +# O2 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_O2=0.02E-06 +## Denitrification +#F switch hard threshold scheme for OM remineralisation +bg_ctrl_bio_remin_thresh = .true. +#F denitrification O2 threshold (40E-6, Naafs etal 2019) +bg_par_bio_remin_cthresh_O2=30E-6 +# +# iron tracer scheme +# NOTE: the base-config requires TFe and TL tracers +bg_opt_geochem_Fe='hybrid' +# exponent for aeolian Fe solubility [use 1.0 for uniform solubility] +bg_par_det_Fe_sol_exp=0.500 +# aeolian Fe solubility +bg_par_det_Fe_sol=0.002441 +# modifier of the scavenging rate of dissolved Fe +bg_par_scav_Fe_sf_POC=0.225 +# no scavenged regeneration +bg_par_scav_fremin=0.0 +# return POFe +bg_ctrl_bio_NO_fsedFe=.false. +# Variable Fe:C +bg_ctrl_bio_red_fixedFetoC=.false. +# adjust pK'(FeL) +bg_par_K_FeL_pP=11.0 +#(max) C/Fe organic matter ratio +bg_par_bio_red_POFe_POC=250000.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- power +bg_par_bio_FetoC_pP=-0.4225 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- scaling +bg_par_bio_FetoC_K=103684.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- constant +bg_par_bio_FetoC_C=0.0 +# +# --- Si ---------------------------------------------- +# +# Si:C [DEFAULT: 0.175] ***** TO CHECK +bg_par_bio_red_POC_opal=0.65 +# remin ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=125.0 +# 30Si ***** TO CHECK +# epsilon 30Si associated with opal formation [DEFAULT: -1.1] +bg_par_d30Si_opal_epsilon=-1.1 +# +# *** ECOGEM ******************************************************** +# +# ecosystem configuration +# PFTs with diatoms, pico and eukaryotes Fanny - Jun20 +eg_par_ecogem_plankton_file ='8P8Z.eco' + +#################### Nitrogen ############################ +eg_useNO3 =.false. +eg_nquota =.false. +################## Phosphorus ############################ +eg_usePO4 =.true. +eg_pquota =.true. +######################## Iron ############################ +eg_useFe =.true. +eg_fquota =.true. +################# Chlorophyll ############################ +eg_chlquota =.true. +################# d13C ################################### +eg_useDIC_13C =.true. +#################### Silicate ############################ +eg_useSiO2 =.true. +eg_squota =.true. + +# Tuned - Ward et al. (2018) +eg_qminP_a = 3.33e-3 +eg_qminFe_a = 1.00e-6 +eg_qmaxFe_a = 4.00e-6 +# Si properties - Fanny June2020 +eg_vmaxSiO2_a=4.4e-2 +eg_vmaxSiO2_b=0.06 +eg_qminSi_a=0.033600 +eg_qmaxSi_a=0.176000 +eg_affinSiO2_a = 3.900 +eg_affinSiO2_b = -0.35 + +# eukaryote photosynthetic rate - Fanny Jun20 (equivalent to 0.56 times diatoms Pmax) +eg_vmaxDIC_a_pft_eukaryote = 2.2000 + +# ??? +eg_ns=2 +# ??? +eg_respir_a=0 +# DOM parameters +eg_beta_mort_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_mort_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_mort_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +eg_beta_graz_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_graz_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_graz_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +# ??? +eg_nsubtime=25 +eg_n_keco=1 +# exponent for modifier of CaCO3:POC export ratio +eg_par_bio_red_POC_CaCO3_pP = 0.7440 # exponent for modifier of CaCO3:POC export ratio +# underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +eg_par_bio_red_POC_CaCO3 = 0.0285 # underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +# +# *** DATA SAVING *************************************************** +# +# BASIC + biology + tracer + proxy diagnostics +bg_par_data_save_level=10 +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst = .false. +eg_ctrl_continuing = .false. +# +# *** FORCINGS ****************************************************** +# +bg_par_forcing_name="worjh2.RpCO2_Rp13CO2.Albani.0ka" +bg_par_atm_force_scale_val_3=278.0E-06 +bg_par_atm_force_scale_val_4=-6.5 +# +# *** MISC ********************************************************** +# +# kraus-turner mixed layer scheme on (1) or off (0) +go_imld = 1 +# *** optional changes to align with PALEO recommendations ********** +# set mixed layer to be only diagnosed (for ECOGEM) +go_ctrl_diagmld=.true. +# add seaice attenuation of PAR +eg_ctrl_PARseaicelimit=.true. +# relative partitioning of C into DOM +#eg_par_beta_POCtoDOC=0.75 +# maximum time-scale to geochemical reaction completion (days) +bg_par_bio_geochem_tau=90.0 +# extend solubility and geochem constant T range (leave S range as default) +gm_par_geochem_Tmin = -2.0 +gm_par_geochem_Tmax = 45.0 +gm_par_carbchem_Tmin = -2.0 +gm_par_carbchem_Tmax = 45.0 +# +# ******************************************************************* +# *** END *********************************************************** +# ******************************************************************* +# +Ensemble created: 180712 ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=83.146 +bg_par_bio_red_POC_opal=0.17185 +Ensemble created: 220224 +eg_qminP_a=0.0027022 +eg_qmaxP_a=0.0216773 +eg_qminFe_a=6.8572e-07 +eg_qmaxFe_a=4.09512e-06 +eg_qminSi_a=0.043259 +eg_qmaxSi_a=0.407638 +eg_affinSiO2_a=4.7769 +eg_affinSiO2_b=-0.40131 +eg_affinPO4_a=0.94403 +eg_affinPO4_b=-0.43718 +eg_affinFe_a=0.17761 +eg_affinFe_b=-0.2574 +eg_vmaxFe_a=0.00016885 +eg_vmaxFe_b=-0.12635 +eg_vmaxSiO2_a=0.068039 +eg_vmaxSiO2_b=0.031868 +eg_par_diatom_palatability_mod=0.92802 +bg_par_bio_remin_sinkingrate_reaction=49.689 diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/NoDiatom b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/NoDiatom new file mode 100644 index 000000000..a0e813fe6 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/NoDiatom @@ -0,0 +1,212 @@ +# ******************************************************************* +# *** Like muffin.CBE.worjh2.BASESFeTDTL.Albani with Si cycle on ********************** +# ******************************************************************* +# +# *** CLIMATE ******************************************************* +# +# set climate feedback (climate responding to changing pCO2) +ea_36=y +# +# *** BIOLOGICAL NEW PRODUCTION ************************************* +# +# biological scheme ID string +# NOTE: with ECOGEM, no BIOGEM biological scheme must be selected +bg_par_bio_prodopt="NONE" +# +# *** ORGANIC MATTER EXPORT RATIOS ********************************** +# +# [dealt with by ECOGEM] +# +# *** INORGANIC MATTER EXPORT RATIOS ******************************** +# +# [dealt with by ECOGEM] +# +# *** REMINERALIZATION ********************************************** +# +# DOC lifetime (yrs) +bg_par_bio_remin_DOMlifetime=0.5 +# initial fractional abundance of POC component #2 +bg_par_bio_remin_POC_frac2=0.0557 +# depth of remineralization or particulate organic matter +bg_par_bio_remin_POC_eL1=589.9451 +# remineralization length #2 for POC +bg_par_bio_remin_POC_eL2=1000000.0 +# initial fractional abundance of CaCO3 component #2 +bg_par_bio_remin_CaCO3_frac2=0.45 +# depth of remineralization or CaCO3 +bg_par_bio_remin_CaCO3_eL1=1.8905e+003 +# remineralization length #2 for CaCO3 +bg_par_bio_remin_CaCO3_eL2=1000000.0 +# *** optional changes to align with PALEO recommendations ********** +# set 'instantaneous' water column remineralziation +bg_par_bio_remin_sinkingrate_physical=9.9E9 +bg_par_bio_remin_sinkingrate_reaction=125.0 +# +# --- NITROGEN ------------------------------------------------------ Fanny - June 2020 +## Nitrification +# NH4 oxidation rate constant (yr-1) +bg_par_nitri_mu=7.30 +# NH4 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_NH4=0.01E-06 +# O2 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_O2=0.02E-06 +## Denitrification +#F switch hard threshold scheme for OM remineralisation +bg_ctrl_bio_remin_thresh = .true. +#F denitrification O2 threshold (40E-6, Naafs etal 2019) +bg_par_bio_remin_cthresh_O2=30E-6 +# +# iron tracer scheme +# NOTE: the base-config requires TFe and TL tracers +bg_opt_geochem_Fe='hybrid' +# exponent for aeolian Fe solubility [use 1.0 for uniform solubility] +bg_par_det_Fe_sol_exp=0.500 +# aeolian Fe solubility +bg_par_det_Fe_sol=0.002441 +# modifier of the scavenging rate of dissolved Fe +bg_par_scav_Fe_sf_POC=0.225 +# no scavenged regeneration +bg_par_scav_fremin=0.0 +# return POFe +bg_ctrl_bio_NO_fsedFe=.false. +# Variable Fe:C +bg_ctrl_bio_red_fixedFetoC=.false. +# adjust pK'(FeL) +bg_par_K_FeL_pP=11.0 +#(max) C/Fe organic matter ratio +bg_par_bio_red_POFe_POC=250000.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- power +bg_par_bio_FetoC_pP=-0.4225 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- scaling +bg_par_bio_FetoC_K=103684.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- constant +bg_par_bio_FetoC_C=0.0 +# +# --- Si ---------------------------------------------- +# +# Si:C [DEFAULT: 0.175] ***** TO CHECK +bg_par_bio_red_POC_opal=0.65 +# remin ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=125.0 +# 30Si ***** TO CHECK +# epsilon 30Si associated with opal formation [DEFAULT: -1.1] +bg_par_d30Si_opal_epsilon=-1.1 +# +# *** ECOGEM ******************************************************** +# +# ecosystem configuration +# PFTs with diatoms, pico and eukaryotes Fanny - Jun20 +eg_par_ecogem_plankton_file ='NoDiat4ZP_PiEu.eco' + +#################### Nitrogen ############################ +eg_useNO3 =.false. +eg_nquota =.false. +################## Phosphorus ############################ +eg_usePO4 =.true. +eg_pquota =.true. +######################## Iron ############################ +eg_useFe =.true. +eg_fquota =.true. +################# Chlorophyll ############################ +eg_chlquota =.true. +################# d13C ################################### +eg_useDIC_13C =.true. +#################### Silicate ############################ +eg_useSiO2 =.true. +eg_squota =.true. + +# Tuned - Ward et al. (2018) +eg_qminP_a = 3.33e-3 +eg_qminFe_a = 1.00e-6 +eg_qmaxFe_a = 4.00e-6 +# Si properties - Fanny June2020 +eg_vmaxSiO2_a=4.4e-2 +eg_vmaxSiO2_b=0.06 +eg_qminSi_a=0.033600 +eg_qmaxSi_a=0.176000 +eg_affinSiO2_a = 3.900 +eg_affinSiO2_b = -0.35 + +# eukaryote photosynthetic rate - Fanny Jun20 (equivalent to 0.56 times diatoms Pmax) +eg_vmaxDIC_a_pft_eukaryote = 2.2000 + +# ??? +eg_ns=2 +# ??? +eg_respir_a=0 +# DOM parameters +eg_beta_mort_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_mort_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_mort_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +eg_beta_graz_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_graz_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_graz_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +# ??? +eg_nsubtime=25 +eg_n_keco=1 +# exponent for modifier of CaCO3:POC export ratio +eg_par_bio_red_POC_CaCO3_pP = 0.7440 # exponent for modifier of CaCO3:POC export ratio +# underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +eg_par_bio_red_POC_CaCO3 = 0.0285 # underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +# +# *** DATA SAVING *************************************************** +# +# BASIC + biology + tracer + proxy diagnostics +bg_par_data_save_level=10 +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst = .false. +eg_ctrl_continuing = .false. +# +# *** FORCINGS ****************************************************** +# +bg_par_forcing_name="worjh2.RpCO2_Rp13CO2.Albani.0ka" +bg_par_atm_force_scale_val_3=278.0E-06 +bg_par_atm_force_scale_val_4=-6.5 +# +# *** MISC ********************************************************** +# +# kraus-turner mixed layer scheme on (1) or off (0) +go_imld = 1 +# *** optional changes to align with PALEO recommendations ********** +# set mixed layer to be only diagnosed (for ECOGEM) +go_ctrl_diagmld=.true. +# add seaice attenuation of PAR +eg_ctrl_PARseaicelimit=.true. +# relative partitioning of C into DOM +#eg_par_beta_POCtoDOC=0.75 +# maximum time-scale to geochemical reaction completion (days) +bg_par_bio_geochem_tau=90.0 +# extend solubility and geochem constant T range (leave S range as default) +gm_par_geochem_Tmin = -2.0 +gm_par_geochem_Tmax = 45.0 +gm_par_carbchem_Tmin = -2.0 +gm_par_carbchem_Tmax = 45.0 +# +# ******************************************************************* +# *** END *********************************************************** +# ******************************************************************* +# +Ensemble created: 180712 ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=83.146 +bg_par_bio_red_POC_opal=0.17185 +Ensemble created: 221224 +eg_qminP_a=0.0027022 +eg_qmaxP_a=0.0216773 +eg_qminFe_a=6.8572e-07 +eg_qmaxFe_a=4.09512e-06 +eg_qminSi_a=0.043259 +eg_qmaxSi_a=0.407638 +eg_affinSiO2_a=4.7769 +eg_affinSiO2_b=-0.40131 +eg_affinPO4_a=0.94403 +eg_affinPO4_b=-0.43718 +eg_affinFe_a=0.17761 +eg_affinFe_b=-0.2574 +eg_vmaxFe_a=0.00016885 +eg_vmaxFe_b=-0.12635 +eg_vmaxSiO2_a=0.068039 +eg_vmaxSiO2_b=0.031868 +eg_par_diatom_palatability_mod=0.92802 +bg_par_bio_remin_sinkingrate_reaction=49.689 diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/diat.worjh2.Albani b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/diat.worjh2.Albani new file mode 100644 index 000000000..919343861 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/diat.worjh2.Albani @@ -0,0 +1,193 @@ +# ******************************************************************* +# *** Like muffin.CBE.worjh2.BASESFeTDTL.Albani with Si cycle on ********************** +# ******************************************************************* +# +# *** CLIMATE ******************************************************* +# +# set climate feedback (climate responding to changing pCO2) +ea_36=y +# +# *** BIOLOGICAL NEW PRODUCTION ************************************* +# +# biological scheme ID string +# NOTE: with ECOGEM, no BIOGEM biological scheme must be selected +bg_par_bio_prodopt="NONE" +# +# *** ORGANIC MATTER EXPORT RATIOS ********************************** +# +# [dealt with by ECOGEM] +# +# *** INORGANIC MATTER EXPORT RATIOS ******************************** +# +# [dealt with by ECOGEM] +# +# *** REMINERALIZATION ********************************************** +# +# DOC lifetime (yrs) +bg_par_bio_remin_DOMlifetime=0.5 +# initial fractional abundance of POC component #2 +bg_par_bio_remin_POC_frac2=0.0557 +# depth of remineralization or particulate organic matter +bg_par_bio_remin_POC_eL1=589.9451 +# remineralization length #2 for POC +bg_par_bio_remin_POC_eL2=1000000.0 +# initial fractional abundance of CaCO3 component #2 +bg_par_bio_remin_CaCO3_frac2=0.45 +# depth of remineralization or CaCO3 +bg_par_bio_remin_CaCO3_eL1=1.8905e+003 +# remineralization length #2 for CaCO3 +bg_par_bio_remin_CaCO3_eL2=1000000.0 +# *** optional changes to align with PALEO recommendations ********** +# set 'instantaneous' water column remineralziation +bg_par_bio_remin_sinkingrate_physical=9.9E9 +bg_par_bio_remin_sinkingrate_reaction=125.0 +# +# --- NITROGEN ------------------------------------------------------ Fanny - June 2020 +## Nitrification +# NH4 oxidation rate constant (yr-1) +bg_par_nitri_mu=7.30 +# NH4 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_NH4=0.01E-06 +# O2 half-saturatation constant for NH4 oxidation (mol kg-1) +bg_par_nitri_c0_O2=0.02E-06 +## Denitrification +#F switch hard threshold scheme for OM remineralisation +bg_ctrl_bio_remin_thresh = .true. +#F denitrification O2 threshold (40E-6, Naafs etal 2019) +bg_par_bio_remin_cthresh_O2=30E-6 +# +# iron tracer scheme +# NOTE: the base-config requires TFe and TL tracers +bg_opt_geochem_Fe='hybrid' +# exponent for aeolian Fe solubility [use 1.0 for uniform solubility] +bg_par_det_Fe_sol_exp=0.500 +# aeolian Fe solubility +bg_par_det_Fe_sol=0.002441 +# modifier of the scavenging rate of dissolved Fe +bg_par_scav_Fe_sf_POC=0.225 +# no scavenged regeneration +bg_par_scav_fremin=0.0 +# return POFe +bg_ctrl_bio_NO_fsedFe=.false. +# Variable Fe:C +bg_ctrl_bio_red_fixedFetoC=.false. +# adjust pK'(FeL) +bg_par_K_FeL_pP=11.0 +#(max) C/Fe organic matter ratio +bg_par_bio_red_POFe_POC=250000.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- power +bg_par_bio_FetoC_pP=-0.4225 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- scaling +bg_par_bio_FetoC_K=103684.0 +#[FeT] dependent Fe:C ratio [Ridgwell, 2001] -- constant +bg_par_bio_FetoC_C=0.0 +# +# --- Si ---------------------------------------------- +# +# Si:C [DEFAULT: 0.175] ***** TO CHECK +bg_par_bio_red_POC_opal=0.65 +# remin ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=125.0 +# 30Si ***** TO CHECK +# epsilon 30Si associated with opal formation [DEFAULT: -1.1] +bg_par_d30Si_opal_epsilon=-1.1 +# +# *** ECOGEM ******************************************************** +# +# ecosystem configuration +# PFTs with diatoms, pico and eukaryotes Fanny - Jun20 +eg_par_ecogem_plankton_file ='3Diat4ZP_PiEu.eco' + +#################### Nitrogen ############################ +eg_useNO3 =.false. +eg_nquota =.false. +################## Phosphorus ############################ +eg_usePO4 =.true. +eg_pquota =.true. +######################## Iron ############################ +eg_useFe =.true. +eg_fquota =.true. +################# Chlorophyll ############################ +eg_chlquota =.true. +################# d13C ################################### +eg_useDIC_13C =.true. +#################### Silicate ############################ +eg_useSiO2 =.true. +eg_squota =.true. + +# Tuned - Ward et al. (2018) +eg_qminP_a = 3.33e-3 +eg_qminFe_a = 1.00e-6 +eg_qmaxFe_a = 4.00e-6 +# Si properties - Fanny June2020 +eg_vmaxSiO2_a=4.4e-2 +eg_vmaxSiO2_b=0.06 +eg_qminSi_a=0.033600 +eg_qmaxSi_a=0.176000 +eg_affinSiO2_a = 3.900 +eg_affinSiO2_b = -0.35 + +# eukaryote photosynthetic rate - Fanny Jun20 (equivalent to 0.56 times diatoms Pmax) +eg_vmaxDIC_a_pft_eukaryote = 2.2000 + +# ??? +eg_ns=2 +# ??? +eg_respir_a=0 +# DOM parameters +eg_beta_mort_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_mort_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_mort_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +eg_beta_graz_a = 0.8 # Maximum fraction to DOM as ESD --> zero +eg_beta_graz_b = 0.4 # Minimum fraction to DOM as ESD --> infinity +eg_beta_graz_c = 100.0 # Size at 50:50 partition (default = 100 µm^3) +# ??? +eg_nsubtime=25 +eg_n_keco=1 +# exponent for modifier of CaCO3:POC export ratio +eg_par_bio_red_POC_CaCO3_pP = 0.7440 # exponent for modifier of CaCO3:POC export ratio +# underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +eg_par_bio_red_POC_CaCO3 = 0.0285 # underlying export CaCO3 as a proportion of particulate organic matter (i.e., CaCO3/POC) +# +# *** DATA SAVING *************************************************** +# +# BASIC + biology + tracer + proxy diagnostics +bg_par_data_save_level=10 +# disable ECOGEM restarts (as not currently coded up / used) +eg_ctrl_ncrst = .false. +eg_ctrl_continuing = .false. +# +# *** FORCINGS ****************************************************** +# +bg_par_forcing_name="worjh2.RpCO2_Rp13CO2.Albani.0ka" +bg_par_atm_force_scale_val_3=278.0E-06 +bg_par_atm_force_scale_val_4=-6.5 +# +# *** MISC ********************************************************** +# +# kraus-turner mixed layer scheme on (1) or off (0) +go_imld = 1 +# *** optional changes to align with PALEO recommendations ********** +# set mixed layer to be only diagnosed (for ECOGEM) +go_ctrl_diagmld=.true. +# add seaice attenuation of PAR +eg_ctrl_PARseaicelimit=.true. +# relative partitioning of C into DOM +eg_par_beta_POCtoDOC=0.75 +# maximum time-scale to geochemical reaction completion (days) +bg_par_bio_geochem_tau=90.0 +# extend solubility and geochem constant T range (leave S range as default) +gm_par_geochem_Tmin = -2.0 +gm_par_geochem_Tmax = 45.0 +gm_par_carbchem_Tmin = -2.0 +gm_par_carbchem_Tmax = 45.0 +# +# ******************************************************************* +# *** END *********************************************************** +# ******************************************************************* +# +Ensemble created: 180712 ***** TO CHECK +bg_ctrl_bio_remin_opal_fixed=.false. +bg_par_bio_remin_sinkingrate=83.146 +bg_par_bio_red_POC_opal=0.17185 diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config new file mode 100644 index 000000000..607c4cc6e --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config @@ -0,0 +1,173 @@ +# ******************************************************************* +# CONFIGURATION TEMPLATE (EMBM + GOLDSTEIN + GOLDSTEIN SEA-ICE + ATCHEM + BIOGEM + ECOGEM) +# ******************************************************************* + +# ******************************************************************* +# GENIE COMPONENT SELECTION +# ******************************************************************* +# make .TRUE. the cGENIE modules to be included +# ******************************************************************* +ma_flag_ebatmos=.TRUE. +ma_flag_goldsteinocean=.TRUE. +ma_flag_goldsteinseaice=.TRUE. +ma_flag_biogem=.TRUE. +ma_flag_atchem=.TRUE. +ma_flag_sedgem=.FALSE. +ma_flag_rokgem=.FALSE. +ma_flag_gemlite=.FALSE. +ma_flag_ecogem=.TRUE. +# ******************************************************************* + +# ******************************************************************* +# GRID & BOUNDARY CONDITION CONFIGURATION +# ******************************************************************* +# insert the automatically generated muffingen parameter list here +# ******************************************************************* +# Topography +ma_fname_topo='worjh2' +# Grid resolution of climate components +GENIENXOPTS='-DGENIENX=36' +GENIENYOPTS='-DGENIENY=36' +GENIENLOPTS='-DGENIENL=1' +GENIENXOPTS='$(DEFINE)GENIENX=36' +GENIENYOPTS='$(DEFINE)GENIENY=36' +GOLDSTEINNLONSOPTS='$(DEFINE)GOLDSTEINNLONS=36' +GOLDSTEINNLATSOPTS='$(DEFINE)GOLDSTEINNLATS=36' +GOLDSTEINNLEVSOPTS='$(DEFINE)GOLDSTEINNLEVS=16' +# Topography for climate components +ea_topo=worjh2 +go_topo=worjh2 +gs_topo=worjh2 +# ******************************************************************* + +# ******************************************************************* +# TRACER CONFIGURATION +# ******************************************************************* +# the total number of tracers includes T and S +# T and S do not need to be explicited selected and initialzied +# ******************************************************************* +# Set number of tracers +GOLDSTEINNTRACSOPTS='$(DEFINE)GOLDSTEINNTRACS=19' +# list selected biogeochemical tracers +gm_atm_select_3=.true. # pCO2 -- 'carbon dioxide (CO2)' +gm_atm_select_4=.true. # pCO2_13C -- 'd13C CO2' +gm_atm_select_6=.true. # pO2 -- 'oxygen (O2)' +gm_atm_select_16=.true. # pH2S -- 'hydrogen sulphide (H2S)' +gm_ocn_select_3=.true. # DIC -- 'dissolved inorganic carbon (DIC)' +gm_ocn_select_4=.true. # DIC_13C -- 'd13C of DIC' +gm_ocn_select_8=.true. # PO4 -- 'dissolved phosphate (PO4)' +gm_ocn_select_10=.true. # O2 -- 'dissolved oxygen (O2)' +gm_ocn_select_12=.true. # ALK -- 'alkalinity (ALK)' +gm_ocn_select_13=.true. # SiO2 -- 'aqueous silicic acid (H4SiO4)' +gm_ocn_select_14=.true. # SiO2_30Si -- 'd30Si of H4SiO4' +gm_ocn_select_15=.true. # DOM_C -- 'dissolved organic matter (DOM); carbon' +gm_ocn_select_16=.true. # DOM_C_13C -- 'd13C of DOM-C' +gm_ocn_select_20=.true. # DOM_P -- 'dissolved organic matter; phosphorous' +gm_ocn_select_22=.true. # DOM_Fe -- 'dissolved organic matter; iron' +gm_ocn_select_90=.true. # TDFe -- 'total dissolved Fe' +gm_ocn_select_42=.true. # TL -- 'total dissolved ligand' +gm_ocn_select_35=.true. # Ca -- 'dissolved calcium (Ca)' +gm_ocn_select_38=.true. # SO4 -- 'dissolved sulphate (SO4)' +gm_ocn_select_40=.true. # H2S -- 'dissolved hydrogen sulphide (H2S)' +gm_ocn_select_50=.true. # Mg -- 'dissolved Magnesium (Mg)' +gm_sed_select_3=.true. # POC -- 'particulate organic carbon (POC)' +gm_sed_select_4=.true. # POC_13C -- 'd13C of POC' +gm_sed_select_8=.true. # POP -- 'particulate organic phosphate (POP)' +gm_sed_select_10=.true. # POFe -- 'particulate organic iron (POFe)' +gm_sed_select_13=.true. # POM_Fe -- 'POM scavenged Fe' +gm_sed_select_14=.true. # CaCO3 -- 'calcium carbonate (CaCO3)' +gm_sed_select_15=.true. # CaCO3_13C -- 'd13C of CaCO3' +gm_sed_select_21=.true. # CaCO3_Fe -- 'CaCO3 scavenged Fe' +gm_sed_select_22=.true. # det -- 'detrital (refractory) material' +gm_sed_select_25=.true. # det_Fe -- 'detrital scavenged Fe' +gm_sed_select_26=.true. # opal -- 'opal' +gm_sed_select_27=.true. # opal_30Si -- 'd30Si of opal' +gm_sed_select_32=.true. # ash -- 'ash' +gm_sed_select_33=.true. # POC_frac2 - 'n/a' +gm_sed_select_34=.true. # CaCO3_frac2 -- 'n/a' +gm_sed_select_35=.true. # opal_frac2 -- 'n/a' +gm_sed_select_36=.true. # CaCO3_age -- 'CaCO3 numerical age tracer' +##gm_ocn_select_66=.true. # Csoft +# list biogeochemical tracer initial values +ac_atm_init_3=278.0E-06 +ac_atm_init_4=-6.5 +ac_atm_init_6=0.2095 +bg_ocn_init_3=2.244E-03 +bg_ocn_init_4=0.4 +bg_ocn_init_8=2.159E-06 +bg_ocn_init_10=1.696E-04 +bg_ocn_init_12=2.363E-03 +bg_ocn_init_13=85.0E-06 +bg_ocn_init_14=1.1 +bg_ocn_init_90=0.650E-09 +bg_ocn_init_42=1.000E-09 +bg_ocn_init_35=1.025E-02 +bg_ocn_init_38=2.916E-02 +bg_ocn_init_50=5.282E-02 +# ******************************************************************* + +# ******************************************************************* +# PHYSICAL CLIMATE CALIBRATION +# ******************************************************************* +# based on Cao et al. [2009] with the following exceptions: +# (1) warmer (5C) ocean start (could be 10C for a more intense greenhouse world) +# (2) scaling of the freshwater re-balancing flux to zero +# (3) application of a reduced sea-ice diffusivity and +# prescribed maximum fractional area for sea-ice advection +# (4) recommended: turn off isoneutral isopycnal/diapycnal mixing scheme +# (5) NOTE: no reduced diffusivity over Antarctica +# ******************************************************************* +# rel +go_12=0.9000000 +# scl_tau / SclTau +go_13=1.531013488769531300 +# ocean diffusivites iso (or horiz) / OcnHorizDiff +go_14=1494.438354492187500000 +# ocean diffusivites dia (or vert) / OcnVertDiff +go_15=0.000025363247914356 +# inverse minimum drag in days / InvDrag +go_16=2.710164785385131800 +# scl_tau (should be same as GOLDSTEIN's value) / SclTau +ea_11=1.531013488769531300 +# atm. diff. amp. for T / AtmDiffAmpT +ea_12=5204945.000000000000000000 +# atm. diff. amp. for q / AtmDiffAmpQ +ea_13=1173269.250000000000000000 +# dist'n width / AtmDiffWidthT +ea_14=1.410347938537597700 +# dist'n slope / AtmDiffSlopeT +ea_15=0.090003050863742828 +# atm. advection factor for T_z / AtmAdvectCoeffTm +ea_16=0.001037851092405617 +# atm. advection factor for T_m / AtmAdvectCoeffQm +ea_17=0.0000000E+00 +# atm. advection factor for q_z / AtmAdvectCoeffQz +ea_18=0.164652019739151000 +# atm. advection factor for q_m / AtmAdvectCoeffQz +ea_19=0.164652019739151000 +# temp0 -- start with a warm ocean +go_10=5.0 +# temp1 -- start with a warm ocean +go_11=5.0 +# SclFWF +ea_28=0.726862013339996340 +# sea-ice eddy diffusivity / SeaiceDiff +gs_11=3573.718017578125000000 +#diffusivity scaling factor +ea_diffa_scl=0.25 +#grid point distance over which scalar is applied (j direction) +ea_diffa_len=3 +# set seasonal cycle +ea_dosc=.true. +go_dosc=.true. +gs_dosc=.true. +# isoneutral isopycnal/diapycnal mixing scheme +# it is recommended that it is turned OFF (=.false.) for 'fake' worlds +go_diso=.true. +# ******************************************************************* + +# ******************************************************************* +# USER-APPENDED OPTIONS FOLLOW ... +# ******************************************************************* +# (the following parameter text is appended automatically) +# ******************************************************************* diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt new file mode 100644 index 000000000..6db01e457 --- /dev/null +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt @@ -0,0 +1,48 @@ +################################################################ +### readme.txt ################################################# +################################################################ + +For: +'A diatom extension of the EcoGEnIE Earth system model - EcoGEnIE 1.1' +Aaron A. Naidoo-Bagwell, Fanny M. Monteiro, Katharine R. Hendry, Scott Burgan, Jamie D. Wilson, Ben A. Ward, Andy Ridgwell and Daniel J. Conley + +################################################################ +15/11/2023 -- README.txt file creation (A.A.N.) +################################################################ + +Provided is the code used to create the model experiments presented in the paper. +Also given are the configuration files necessary to run the model experiments. + +### model experiments -- spinups ############################### + +All experiments are run from: +$HOME/cgenie.muffin/genie-main +(unless a different installation directory has been used) + +The commands to run the model configurations are listed as follows: + +Ensure base config muffin.CBE.worjh2.BASESFeTDTLSi.Albani is in cgenie.muffin/genie-main/configs +Ensure config file 3Diat_4ZP_PiEu.eco is in cgenie.muffin/genie-ecogem/data + +Initial new physics spin : + +./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 diat.worjh2.Albani 20000 + +Once the spin has completed: + +(1) EcoGEnIE 1.1 2,000 year run + +./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 EcoGEnIE1.1 2000 diat.worjh2.Albani + +(2) EcoGEnIE 1.0 from Ward et al. (2018) + +./runmuffin.sh muffin.CBE.worlg4.BASESFeTDTL MS/wardetal.2018 wardetal.2018.ECOGEM.SPIN 10000 + +(3) Additional runs + +./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 NoDiatom 2000 diat.worjh2.Albani +./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 EcoGEnIE1.1_phys 2000 diat.worjh2.Albani +./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 EcoGEnIE1.1_phys_eco 2000 diat.worjh2.Albani +################################################################ +################################################################ +################################################################ From 194c7e3d560cdc0ac13f88ae7ae2b978ede8ec36 Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:43:27 -0800 Subject: [PATCH 2/7] Delete genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco --- .../3Diat_4ZP_PiEu.eco | 45 ------------------- 1 file changed, 45 deletions(-) delete mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco deleted file mode 100644 index 2231035f5..000000000 --- a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/3Diat_4ZP_PiEu.eco +++ /dev/null @@ -1,45 +0,0 @@ - - 01 02 03 - \/ \/ \/ - --START-OF-DATA- - Diatom 2.00 1 - Diatom 20.00 1 - Diatom 200.00 1 - Picoplankton 0.6 1 - Picoplankton 2.00 1 - Eukaryote 20.00 1 - Eukaryote 200.00 1 - Zooplankton 6.00 1 - Zooplankton 20.00 1 - Zooplankton 200.00 1 - Zooplankton 2000.00 1 --END-OF-DATA- - - /\ /\ /\ - 01 02 03 - -DATA FORMAT AND ORDER ---------------------- - -COLUMN #01: plankton functional type name -COLUMN #02: plankton diameter (micrometers) -COLUMN #03: number of randomised replicates - -INFO: TRACER ASSIGNMENT RULES ------------------------------ -Plankton functional type one of: Prochlorococcus - Synechococcus - Picoeukaryote - Picoplankton - Diatom - Coccolithophore - Diazotroph - Eukaryote - Phytoplankton - Zooplankton - Mixotroph - - - - From 6d2d7766446e118128f706d563b21a18dd437f9f Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:43:57 -0800 Subject: [PATCH 3/7] Delete genie-ecogem/data/input/3Diat_4ZP_PiEu.eco --- genie-ecogem/data/input/3Diat_4ZP_PiEu.eco | 45 ---------------------- 1 file changed, 45 deletions(-) delete mode 100644 genie-ecogem/data/input/3Diat_4ZP_PiEu.eco diff --git a/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco b/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco deleted file mode 100644 index 2231035f5..000000000 --- a/genie-ecogem/data/input/3Diat_4ZP_PiEu.eco +++ /dev/null @@ -1,45 +0,0 @@ - - 01 02 03 - \/ \/ \/ - --START-OF-DATA- - Diatom 2.00 1 - Diatom 20.00 1 - Diatom 200.00 1 - Picoplankton 0.6 1 - Picoplankton 2.00 1 - Eukaryote 20.00 1 - Eukaryote 200.00 1 - Zooplankton 6.00 1 - Zooplankton 20.00 1 - Zooplankton 200.00 1 - Zooplankton 2000.00 1 --END-OF-DATA- - - /\ /\ /\ - 01 02 03 - -DATA FORMAT AND ORDER ---------------------- - -COLUMN #01: plankton functional type name -COLUMN #02: plankton diameter (micrometers) -COLUMN #03: number of randomised replicates - -INFO: TRACER ASSIGNMENT RULES ------------------------------ -Plankton functional type one of: Prochlorococcus - Synechococcus - Picoeukaryote - Picoplankton - Diatom - Coccolithophore - Diazotroph - Eukaryote - Phytoplankton - Zooplankton - Mixotroph - - - - From 211bd6bcc5706b184dd3a300c11343d50c7e1ebb Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:44:22 -0800 Subject: [PATCH 4/7] Add files via upload --- genie-ecogem/data/input/3Diat4ZP_PiEu.eco | 41 ++++++++++++++++++++++ genie-ecogem/data/input/NoDiat4ZP_PiEu.eco | 38 ++++++++++++++++++++ 2 files changed, 79 insertions(+) create mode 100644 genie-ecogem/data/input/3Diat4ZP_PiEu.eco create mode 100644 genie-ecogem/data/input/NoDiat4ZP_PiEu.eco diff --git a/genie-ecogem/data/input/3Diat4ZP_PiEu.eco b/genie-ecogem/data/input/3Diat4ZP_PiEu.eco new file mode 100644 index 000000000..711d9cdc8 --- /dev/null +++ b/genie-ecogem/data/input/3Diat4ZP_PiEu.eco @@ -0,0 +1,41 @@ + + 01 02 03 + \/ \/ \/ + +-START-OF-DATA- + Diatom 2.00 1 + Diatom 20.00 1 + Diatom 200.00 1 + Picoplankton 0.6 1 + Picoplankton 2.00 1 + Eukaryote 20.00 1 + Eukaryote 200.00 1 + Zooplankton 6.00 1 + Zooplankton 20.00 1 + Zooplankton 200.00 1 + Zooplankton 2000.00 1 +-END-OF-DATA- + + /\ /\ /\ + 01 02 03 + +DATA FORMAT AND ORDER +--------------------- + +COLUMN #01: plankton functional type name +COLUMN #02: plankton diameter (micrometers) +COLUMN #03: number of randomised replicates + +INFO: TRACER ASSIGNMENT RULES +----------------------------- +Plankton functional type one of: Prochlorococcus + Synechococcus + Picoeukaryote + Picoplankton + Diatom + Coccolithophore + Diazotroph + Eukaryote + Phytoplankton + Zooplankton + Mixotroph diff --git a/genie-ecogem/data/input/NoDiat4ZP_PiEu.eco b/genie-ecogem/data/input/NoDiat4ZP_PiEu.eco new file mode 100644 index 000000000..4e35a6a06 --- /dev/null +++ b/genie-ecogem/data/input/NoDiat4ZP_PiEu.eco @@ -0,0 +1,38 @@ + + 01 02 03 + \/ \/ \/ + +-START-OF-DATA- + Picoplankton 0.6 1 + Picoplankton 2.00 1 + Eukaryote 20.00 1 + Eukaryote 200.00 1 + Zooplankton 6.00 1 + Zooplankton 20.00 1 + Zooplankton 200.00 1 + Zooplankton 2000.00 1 +-END-OF-DATA- + + /\ /\ /\ + 01 02 03 + +DATA FORMAT AND ORDER +--------------------- + +COLUMN #01: plankton functional type name +COLUMN #02: plankton diameter (micrometers) +COLUMN #03: number of randomised replicates + +INFO: TRACER ASSIGNMENT RULES +----------------------------- +Plankton functional type one of: Prochlorococcus + Synechococcus + Picoeukaryote + Picoplankton + Diatom + Coccolithophore + Diazotroph + Eukaryote + Phytoplankton + Zooplankton + Mixotroph From a4cf9afa9037084f8fd8f31cde00102bcd71aa72 Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:49:02 -0800 Subject: [PATCH 5/7] Update EcoGEnIE1.1 --- .../PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 index 8031867b1..b777f14bf 100644 --- a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/EcoGEnIE1.1 @@ -97,7 +97,7 @@ bg_par_d30Si_opal_epsilon=-1.1 # # ecosystem configuration # PFTs with diatoms, pico and eukaryotes Fanny - Jun20 -eg_par_ecogem_plankton_file ='3Diat_4ZP_PiEu.eco' +eg_par_ecogem_plankton_file ='3Diat4ZP_PiEu.eco' #################### Nitrogen ############################ eg_useNO3 =.false. From 55b73b3d8d59e8831a34f96aba622dec810b52b0 Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:50:38 -0800 Subject: [PATCH 6/7] Delete genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config --- ...fin.CBE.worjh2.BASESFeTDTLSi.Albani.config | 173 ------------------ 1 file changed, 173 deletions(-) delete mode 100644 genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config deleted file mode 100644 index 607c4cc6e..000000000 --- a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/muffin.CBE.worjh2.BASESFeTDTLSi.Albani.config +++ /dev/null @@ -1,173 +0,0 @@ -# ******************************************************************* -# CONFIGURATION TEMPLATE (EMBM + GOLDSTEIN + GOLDSTEIN SEA-ICE + ATCHEM + BIOGEM + ECOGEM) -# ******************************************************************* - -# ******************************************************************* -# GENIE COMPONENT SELECTION -# ******************************************************************* -# make .TRUE. the cGENIE modules to be included -# ******************************************************************* -ma_flag_ebatmos=.TRUE. -ma_flag_goldsteinocean=.TRUE. -ma_flag_goldsteinseaice=.TRUE. -ma_flag_biogem=.TRUE. -ma_flag_atchem=.TRUE. -ma_flag_sedgem=.FALSE. -ma_flag_rokgem=.FALSE. -ma_flag_gemlite=.FALSE. -ma_flag_ecogem=.TRUE. -# ******************************************************************* - -# ******************************************************************* -# GRID & BOUNDARY CONDITION CONFIGURATION -# ******************************************************************* -# insert the automatically generated muffingen parameter list here -# ******************************************************************* -# Topography -ma_fname_topo='worjh2' -# Grid resolution of climate components -GENIENXOPTS='-DGENIENX=36' -GENIENYOPTS='-DGENIENY=36' -GENIENLOPTS='-DGENIENL=1' -GENIENXOPTS='$(DEFINE)GENIENX=36' -GENIENYOPTS='$(DEFINE)GENIENY=36' -GOLDSTEINNLONSOPTS='$(DEFINE)GOLDSTEINNLONS=36' -GOLDSTEINNLATSOPTS='$(DEFINE)GOLDSTEINNLATS=36' -GOLDSTEINNLEVSOPTS='$(DEFINE)GOLDSTEINNLEVS=16' -# Topography for climate components -ea_topo=worjh2 -go_topo=worjh2 -gs_topo=worjh2 -# ******************************************************************* - -# ******************************************************************* -# TRACER CONFIGURATION -# ******************************************************************* -# the total number of tracers includes T and S -# T and S do not need to be explicited selected and initialzied -# ******************************************************************* -# Set number of tracers -GOLDSTEINNTRACSOPTS='$(DEFINE)GOLDSTEINNTRACS=19' -# list selected biogeochemical tracers -gm_atm_select_3=.true. # pCO2 -- 'carbon dioxide (CO2)' -gm_atm_select_4=.true. # pCO2_13C -- 'd13C CO2' -gm_atm_select_6=.true. # pO2 -- 'oxygen (O2)' -gm_atm_select_16=.true. # pH2S -- 'hydrogen sulphide (H2S)' -gm_ocn_select_3=.true. # DIC -- 'dissolved inorganic carbon (DIC)' -gm_ocn_select_4=.true. # DIC_13C -- 'd13C of DIC' -gm_ocn_select_8=.true. # PO4 -- 'dissolved phosphate (PO4)' -gm_ocn_select_10=.true. # O2 -- 'dissolved oxygen (O2)' -gm_ocn_select_12=.true. # ALK -- 'alkalinity (ALK)' -gm_ocn_select_13=.true. # SiO2 -- 'aqueous silicic acid (H4SiO4)' -gm_ocn_select_14=.true. # SiO2_30Si -- 'd30Si of H4SiO4' -gm_ocn_select_15=.true. # DOM_C -- 'dissolved organic matter (DOM); carbon' -gm_ocn_select_16=.true. # DOM_C_13C -- 'd13C of DOM-C' -gm_ocn_select_20=.true. # DOM_P -- 'dissolved organic matter; phosphorous' -gm_ocn_select_22=.true. # DOM_Fe -- 'dissolved organic matter; iron' -gm_ocn_select_90=.true. # TDFe -- 'total dissolved Fe' -gm_ocn_select_42=.true. # TL -- 'total dissolved ligand' -gm_ocn_select_35=.true. # Ca -- 'dissolved calcium (Ca)' -gm_ocn_select_38=.true. # SO4 -- 'dissolved sulphate (SO4)' -gm_ocn_select_40=.true. # H2S -- 'dissolved hydrogen sulphide (H2S)' -gm_ocn_select_50=.true. # Mg -- 'dissolved Magnesium (Mg)' -gm_sed_select_3=.true. # POC -- 'particulate organic carbon (POC)' -gm_sed_select_4=.true. # POC_13C -- 'd13C of POC' -gm_sed_select_8=.true. # POP -- 'particulate organic phosphate (POP)' -gm_sed_select_10=.true. # POFe -- 'particulate organic iron (POFe)' -gm_sed_select_13=.true. # POM_Fe -- 'POM scavenged Fe' -gm_sed_select_14=.true. # CaCO3 -- 'calcium carbonate (CaCO3)' -gm_sed_select_15=.true. # CaCO3_13C -- 'd13C of CaCO3' -gm_sed_select_21=.true. # CaCO3_Fe -- 'CaCO3 scavenged Fe' -gm_sed_select_22=.true. # det -- 'detrital (refractory) material' -gm_sed_select_25=.true. # det_Fe -- 'detrital scavenged Fe' -gm_sed_select_26=.true. # opal -- 'opal' -gm_sed_select_27=.true. # opal_30Si -- 'd30Si of opal' -gm_sed_select_32=.true. # ash -- 'ash' -gm_sed_select_33=.true. # POC_frac2 - 'n/a' -gm_sed_select_34=.true. # CaCO3_frac2 -- 'n/a' -gm_sed_select_35=.true. # opal_frac2 -- 'n/a' -gm_sed_select_36=.true. # CaCO3_age -- 'CaCO3 numerical age tracer' -##gm_ocn_select_66=.true. # Csoft -# list biogeochemical tracer initial values -ac_atm_init_3=278.0E-06 -ac_atm_init_4=-6.5 -ac_atm_init_6=0.2095 -bg_ocn_init_3=2.244E-03 -bg_ocn_init_4=0.4 -bg_ocn_init_8=2.159E-06 -bg_ocn_init_10=1.696E-04 -bg_ocn_init_12=2.363E-03 -bg_ocn_init_13=85.0E-06 -bg_ocn_init_14=1.1 -bg_ocn_init_90=0.650E-09 -bg_ocn_init_42=1.000E-09 -bg_ocn_init_35=1.025E-02 -bg_ocn_init_38=2.916E-02 -bg_ocn_init_50=5.282E-02 -# ******************************************************************* - -# ******************************************************************* -# PHYSICAL CLIMATE CALIBRATION -# ******************************************************************* -# based on Cao et al. [2009] with the following exceptions: -# (1) warmer (5C) ocean start (could be 10C for a more intense greenhouse world) -# (2) scaling of the freshwater re-balancing flux to zero -# (3) application of a reduced sea-ice diffusivity and -# prescribed maximum fractional area for sea-ice advection -# (4) recommended: turn off isoneutral isopycnal/diapycnal mixing scheme -# (5) NOTE: no reduced diffusivity over Antarctica -# ******************************************************************* -# rel -go_12=0.9000000 -# scl_tau / SclTau -go_13=1.531013488769531300 -# ocean diffusivites iso (or horiz) / OcnHorizDiff -go_14=1494.438354492187500000 -# ocean diffusivites dia (or vert) / OcnVertDiff -go_15=0.000025363247914356 -# inverse minimum drag in days / InvDrag -go_16=2.710164785385131800 -# scl_tau (should be same as GOLDSTEIN's value) / SclTau -ea_11=1.531013488769531300 -# atm. diff. amp. for T / AtmDiffAmpT -ea_12=5204945.000000000000000000 -# atm. diff. amp. for q / AtmDiffAmpQ -ea_13=1173269.250000000000000000 -# dist'n width / AtmDiffWidthT -ea_14=1.410347938537597700 -# dist'n slope / AtmDiffSlopeT -ea_15=0.090003050863742828 -# atm. advection factor for T_z / AtmAdvectCoeffTm -ea_16=0.001037851092405617 -# atm. advection factor for T_m / AtmAdvectCoeffQm -ea_17=0.0000000E+00 -# atm. advection factor for q_z / AtmAdvectCoeffQz -ea_18=0.164652019739151000 -# atm. advection factor for q_m / AtmAdvectCoeffQz -ea_19=0.164652019739151000 -# temp0 -- start with a warm ocean -go_10=5.0 -# temp1 -- start with a warm ocean -go_11=5.0 -# SclFWF -ea_28=0.726862013339996340 -# sea-ice eddy diffusivity / SeaiceDiff -gs_11=3573.718017578125000000 -#diffusivity scaling factor -ea_diffa_scl=0.25 -#grid point distance over which scalar is applied (j direction) -ea_diffa_len=3 -# set seasonal cycle -ea_dosc=.true. -go_dosc=.true. -gs_dosc=.true. -# isoneutral isopycnal/diapycnal mixing scheme -# it is recommended that it is turned OFF (=.false.) for 'fake' worlds -go_diso=.true. -# ******************************************************************* - -# ******************************************************************* -# USER-APPENDED OPTIONS FOLLOW ... -# ******************************************************************* -# (the following parameter text is appended automatically) -# ******************************************************************* From dc2d31b3f83adb17e35b5cbfa9c52d3640f3ae82 Mon Sep 17 00:00:00 2001 From: Andy Ridgwell Date: Wed, 22 Nov 2023 13:51:22 -0800 Subject: [PATCH 7/7] Update readme.txt --- .../PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt index 6db01e457..2544c638a 100644 --- a/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt +++ b/genie-userconfigs/PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023/readme.txt @@ -21,9 +21,6 @@ $HOME/cgenie.muffin/genie-main The commands to run the model configurations are listed as follows: -Ensure base config muffin.CBE.worjh2.BASESFeTDTLSi.Albani is in cgenie.muffin/genie-main/configs -Ensure config file 3Diat_4ZP_PiEu.eco is in cgenie.muffin/genie-ecogem/data - Initial new physics spin : ./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 diat.worjh2.Albani 20000 @@ -43,6 +40,7 @@ Once the spin has completed: ./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 NoDiatom 2000 diat.worjh2.Albani ./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 EcoGEnIE1.1_phys 2000 diat.worjh2.Albani ./runmuffin.sh muffin.CBE.worjh2.BASESFeTDTLSi.Albani PUBS/submitted/Naidoo-Bagwell_et_al.GMD.2023 EcoGEnIE1.1_phys_eco 2000 diat.worjh2.Albani + ################################################################ ################################################################ ################################################################