Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 14 additions & 4 deletions genie-ecogem/src/fortran/ecogem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,8 +84,8 @@ subroutine ecogem( &
REAL,DIMENSION(iomax,npmax) ::AP_uptake ! Auto uptake for each plankton
REAL,DIMENSION(iomax,npmax) ::HP_uptake ! Auto uptake for each plankton
!REAL,DIMENSION(npmax) ::diameter !ckc for size dependent fractionation

REAL,DIMENSION(npmax) ::mortality,respiration
REAL,DIMENSION(npmax) ::mort_loss, respir_loss, eaten_loss ! real-time carbon biomass loss
REAL,DIMENSION(npmax) ::beta_mort_1,beta_graz_1
REAL,DIMENSION(iomax+iChl,npmax) ::assimilated,unassimilated
REAL,DIMENSION(npmax) ::BioC,PP
Expand Down Expand Up @@ -323,7 +323,7 @@ subroutine ecogem( &
PAR_out = PAR_in * exp(-k_tot*layerthick) ! light leaving bottom of layer
PAR_in = PAR_out
endif

! ?
up_inorg(:,:) = 0.0 ! (iomax,npmax)
qreg(:,:) = 0.0 ! (iomax,npmax)
Expand All @@ -347,7 +347,7 @@ subroutine ecogem( &
call quota_limitation(quota,limit,VLlimit,qreg,qreg_h)

call t_limitation(templocal,gamma_TP,gamma_TK)

call nutrient_uptake(qreg(:,:),loc_nuts(:),gamma_TK,up_inorg(:,:))

call photosynthesis(PAR_layer,loc_biomass,limit,VLlimit,up_inorg,gamma_TP,up_inorg(iDIC,:),chlsynth,totPP)
Expand All @@ -373,7 +373,7 @@ subroutine ecogem( &
! mortality(:) = mortality(:) * gamma_TK ! temp adjusted?

! calculate respiration
respiration(:) = respir(:) !* (1.0 - exp(-1.0e10 * loc_biomass(iCarb,:))) ! reduce respiration at very low biomass
respiration(:) = respir(:) * gamma_TK !* (1.0 - exp(-1.0e10 * loc_biomass(iCarb,:))) ! reduce respiration at very low biomass

! calculate assimilation efficiency based on quota status
!BAW: zoolimit should be optional Totzoolimit(:) = 0.0 !total food limitation - Maria May 2019 !!! Need to check if consistent!!!
Expand Down Expand Up @@ -458,6 +458,9 @@ subroutine ecogem( &
do io=1,iomax
AP_uptake(io,:) = dbiomassdt(io,:)
HP_uptake(io,:) = GrazPredEat(io,:) * assimilated(io,:)
mort_loss(:) = mortality(:) * BioC(:)
respir_loss(:) = respiration(:) * BioC(:)
eaten_loss(:)= GrazPreyEaten(iCarb, :)
enddo
endif

Expand Down Expand Up @@ -627,6 +630,10 @@ subroutine ecogem( &
if (eco_uptake_fluxes) then
AP_flux(io,:,i,j,k) = AP_uptake(io,:) ! mmol/m^3/s
HP_flux(io,:,i,j,k) = HP_uptake(io,:) ! mmol/m^3/s
! save the global biomass loss fluxes
plankton_mort(:,i,j,k) = mort_loss(:)
plankton_eaten(:,i,j,k) = eaten_loss(:)
plankton_respir(:,i,j,k) = respir_loss(:)
end if
enddo

Expand Down Expand Up @@ -914,6 +921,9 @@ SUBROUTINE diag_ecogem_timeslice( &
if (eco_uptake_fluxes) then
int_AP_timeslice(:,:,:,:,:) = int_AP_timeslice(:,:,:,:,:) + loc_dtyr * AP_flux(:,:,:,:,:) * pday ! mmol m^-3 d^-1 autotrophic flux in each plankton
int_HP_timeslice(:,:,:,:,:) = int_HP_timeslice(:,:,:,:,:) + loc_dtyr * HP_flux(:,:,:,:,:) * pday ! mmol m^-3 d^-1 heterotrophic flux in each plankton
int_pmort_timeslice(:,:,:,:) = int_pmort_timeslice(:,:,:,:) + loc_dtyr * plankton_mort(:,:,:,:) * pday ! mmol C m^-3 d^-1 plankton mortality flux in each plankton
int_peaten_timeslice(:,:,:,:) = int_peaten_timeslice(:,:,:,:) + loc_dtyr * plankton_eaten(:,:,:,:) * pday ! mmol C m^-3 d^-1 plankton grazing flux in each plankton
int_prespir_timeslice(:,:,:,:) = int_prespir_timeslice(:,:,:,:) + loc_dtyr * plankton_respir(:,:,:,:) * pday ! mmol C m^-3 d^-1 plankton respiration flux in each plankton
end if
end if

Expand Down
521 changes: 410 additions & 111 deletions genie-ecogem/src/fortran/ecogem_data.f90

Large diffs are not rendered by default.

35 changes: 33 additions & 2 deletions genie-ecogem/src/fortran/ecogem_data_netCDF.f90
Original file line number Diff line number Diff line change
Expand Up @@ -488,6 +488,7 @@ SUBROUTINE sub_save_netcdf_2d()
real::shannon(n_i,n_j),simpson(n_i,n_j),nthresh(n_i,n_j),berger(n_i,n_j)
real::picochl(n_i,n_j),nanochl(n_i,n_j),microchl(n_i,n_j)
real::nphyto

!-----------------------------------------------------------------------
! INITIALIZE LOCAL VARIABLES
!-----------------------------------------------------------------------
Expand Down Expand Up @@ -551,8 +552,38 @@ SUBROUTINE sub_save_netcdf_2d()
write (longstrng, "(A,A31,I3.3,A2,A,A8,A,A1)") trim(adjustl(quotastrng(io))),' Heterotrophic Uptake - Popn. #',jp,' (',trim(adjustl(diamtr)),' micron ',trim(pft(jp)),')'
call sub_adddef_netcdf(loc_iou,3,'eco2D'//shrtstrng,longstrng,trim(quotaunits(io))//' d^-1',loc_c0,loc_c0)
call sub_putvar2d('eco2D'//shrtstrng,loc_iou,n_i,n_j,loc_ntrec,loc_ij(:,:),loc_mask(:,:))
endif
endif
endif

! only export carbon loss
if (io .eq. iCarb) then

loc_ij(:,:) = int_peaten_timeslice(jp,:,:,n_k)
! short string: eco2D_Eaten_C_001
! unit formatter: A2,A,A8,A,A1
write (shrtstrng, "(A5, A7, A, A1, I3.3)") 'eco2D','_Eaten_',trim(adjustl(quotastrng(io))),'_',jp
write (longstrng, "(A, A16,I3.3,A2,A,A8,A,A1)") trim(adjustl(quotastrng(io))),' Grazed - Popn. #',jp,' (',trim(adjustl(diamtr)),' micron ',trim(pft(jp)),')'
call sub_adddef_netcdf(loc_iou,3,shrtstrng,longstrng,trim(quotaunits(io))//' d^-1',loc_c0,loc_c0)
call sub_putvar2d(shrtstrng,loc_iou,n_i,n_j,loc_ntrec,loc_ij(:,:),loc_mask(:,:))

!short string: eco2D_Mortality_C_001
loc_ij(:,:) = int_pmort_timeslice(jp,:,:,n_k)
write (shrtstrng, "(A5, A11, A, A1, I3.3)") 'eco2D','_Mortality_',trim(adjustl(quotastrng(io))),'_',jp
write (longstrng, "(A, A20,I3.3,A2,A,A8,A,A1)") trim(adjustl(quotastrng(io))),' Mortality - Popn. #',jp,' (',trim(adjustl(diamtr)),' micron ',trim(pft(jp)),')'
call sub_adddef_netcdf(loc_iou,3,shrtstrng,longstrng,trim(quotaunits(io))//' d^-1',loc_c0,loc_c0)
call sub_putvar2d(shrtstrng,loc_iou,n_i,n_j,loc_ntrec,loc_ij(:,:),loc_mask(:,:))

!short string: eco2D_Respiration_C_001
loc_ij(:,:) = int_prespir_timeslice(jp,:,:,n_k)
write (shrtstrng, "(A5, A13, A, A1, I3.3)") 'eco2D','_Respiration_',trim(adjustl(quotastrng(io))),'_',jp
write (longstrng, "(A,A22,I3.3,A2,A,A8,A,A1)") trim(adjustl(quotastrng(io))),' Respiration - Popn. #',jp,' (',trim(adjustl(diamtr)),' micron ',trim(pft(jp)),')'
call sub_adddef_netcdf(loc_iou,3,shrtstrng,longstrng,trim(quotaunits(io))//' d^-1',loc_c0,loc_c0)
call sub_putvar2d(shrtstrng,loc_iou,n_i,n_j,loc_ntrec,loc_ij(:,:),loc_mask(:,:))

endif
endif



end do
! Write community total biomasses and inorganic resource fluxes
write (shrtstrng, "(A10,A,A6)") "_Plankton_",trim(adjustl(quotastrng(io))),"_Total"
Expand Down
20 changes: 18 additions & 2 deletions genie-ecogem/src/fortran/ecogem_lib.f90
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,13 @@ MODULE ecogem_lib
! Mixotrophy parameters
real :: trophic_tradeoff
namelist/ini_ecogem_nml/trophic_tradeoff
! foramecogenie parameters (11)
logical::ctrl_use_foramecogenie
real :: foram_auto_cost, foram_hetero_cost
real :: foram_spine_scale, foram_symbiont_esd_scale
namelist/ini_ecogem_nml/foram_auto_cost, foram_hetero_cost
namelist/ini_ecogem_nml/foram_spine_scale, foram_symbiont_esd_scale
namelist/ini_ecogem_nml/ctrl_use_foramecogenie
! Temperature dependence
real :: temp_A,temp_P,temp_K,temp_T0 !
namelist/ini_ecogem_nml/temp_A,temp_P,temp_K,temp_T0
Expand Down Expand Up @@ -290,6 +297,9 @@ MODULE ecogem_lib
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:)::export_flux ! surface export flux for each plankton (iomax,npmax,i,j,k) Fanny/Maria - Aug19
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:)::AP_flux ! surface autotrophic flux for each plankton (iomax,npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:)::HP_flux ! surface heterotrophic flux for each plankton (iomax,npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:):: plankton_respir ! respiration carbon flux for each plankton (npmax,i,j,k), RY, Oct 2023
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:):: plankton_mort ! mortality carbon flux for each plankton (npmax,i,j,k), RY, Oct 2023
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:):: plankton_eaten !grazed carbon flux for each plankton (npmax,i,j,k), RY, Oct 2023
!ckc isotope uptake flux array, to trace full food web interaction
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:)::up_flux_iso !ckc rate of upstake isotopes (iimaxiso,npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:) ::eco_carb ! carbonate chemistry variables
Expand All @@ -305,7 +315,7 @@ MODULE ecogem_lib
character(len=5) ,ALLOCATABLE,DIMENSION(:) ::rsrcstrng ! Inorganic resource labels
INTEGER ,ALLOCATABLE,DIMENSION(:) ::random_n ! n population replicates
INTEGER ,ALLOCATABLE,DIMENSION(:) ::nut2quota ! match nutrients to quotas
REAL ,ALLOCATABLE,DIMENSION(:) ::volume,diameter ,logvol,logesd ! Size parameters
REAL ,ALLOCATABLE,DIMENSION(:) ::volume,diameter,logvol,logesd ! Size parameters
REAL ,ALLOCATABLE,DIMENSION(:) ::autotrophy,heterotrophy ! Trophic strategy
LOGICAL ,ALLOCATABLE,DIMENSION(:) ::herbivory,carnivory ! Feeding behavior - Added by Grigoratou, Nov18
real ,ALLOCATABLE,DIMENSION(:) ::pp_opt_a_array,pp_sig_a_array,ns_array ! grazing parameters as arrays
Expand All @@ -318,6 +328,10 @@ MODULE ecogem_lib
REAL ,ALLOCATABLE,DIMENSION(:) ::qcarbon,alphachl ! Carbon quota and Photosynthesis parameters
REAL ,ALLOCATABLE,DIMENSION(:) ::graz,kg,pp_opt,pp_sig ! Grazing parameters
REAL ,ALLOCATABLE,DIMENSION(:) ::respir,biosink,mort,beta_graz,beta_mort ! Other loss parameters
REAL ,ALLOCATABLE,DIMENSION(:) ::symbiont_auto_cost, symbiont_hetero_cost ! RY, foramecogenie symbiont cost parameter
REAL ,ALLOCATABLE,DIMENSION(:) ::auto_volume, spine_esd_scale, symbiont_esd_scale ! RY, foramecogenie size parameter
REAL ,ALLOCATABLE,DIMENSION(:) ::respir_cost ! RY, foramecogenie grazing parameter

! Grazing kernel
REAL,ALLOCATABLE,DIMENSION(:,:)::gkernel,gkernelT
! netCDF and netCDF restart parameters
Expand Down Expand Up @@ -348,7 +362,6 @@ MODULE ecogem_lib
real::par_misc_t_err !
LOGICAL::par_misc_t_go = .FALSE. !
LOGICAL::par_misc_t_echo_header = .TRUE. !
!
real::par_misc_t_tseries = 0.0
real::par_misc_t_tslice = 0.0
logical::par_misc_t_intseries = .FALSE.
Expand Down Expand Up @@ -385,6 +398,9 @@ MODULE ecogem_lib
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:) ::int_export_timeslice ! Surface export flux for each plankton (iomax,npmax,i,j,k) Fanny/Maria - Aug19
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:) ::int_AP_timeslice ! Surface autotrophic uptake flux for each plankton (iomax,npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:,:) ::int_HP_timeslice ! Surface heterotrophic uptake flux for each plankton (iomax,npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:) ::int_peaten_timeslice ! Surface grazed (carbon) flux for each plankton (npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:) ::int_pmort_timeslice ! Surface mortality (carbon) flux for each plankton (npmax,i,j,k)
REAL ,ALLOCATABLE,DIMENSION(:,:,:,:) ::int_prespir_timeslice ! Surface respiration (carbon) flux for each plankton (npmax,i,j,k)

! ### ADD ADDITIONAL TIME-SLICE ARRAY DEFINITIONS HERE ######################################################################### !

Expand Down
44 changes: 41 additions & 3 deletions genie-ecogem/src/fortran/initialise_ecogem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,18 @@ SUBROUTINE initialise_ecogem( &
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(HP_flux(iomax,npmax,n_i,n_j,n_k),STAT=alloc_error) ! Hetero flux per plankton type
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(plankton_eaten(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(plankton_mort(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(plankton_respir(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(int_pmort_timeslice(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(int_prespir_timeslice(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
ALLOCATE(int_peaten_timeslice(npmax,n_i,n_j,n_k),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

! ecogem time-slice arrays
ALLOCATE(int_plankton_timeslice(iomax+iChl,npmax,n_i,n_j,n_k),STAT=alloc_error)
Expand Down Expand Up @@ -324,6 +336,28 @@ SUBROUTINE initialise_ecogem( &
if (useFe ) rsrcstrng(iFe) = 'Fe'
if (useSiO2 ) rsrcstrng(iSiO2) = 'SiO2'

! foramecogenie arrays allocation
if (ctrl_use_foramecogenie) then

ALLOCATE(respir_cost(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

ALLOCATE(auto_volume(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

ALLOCATE(spine_esd_scale(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

ALLOCATE(symbiont_esd_scale(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

ALLOCATE(symbiont_auto_cost(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)

ALLOCATE(symbiont_hetero_cost(npmax),STAT=alloc_error)
call check_iostat(alloc_error,__LINE__,__FILE__)
endif

! ---------------------------------------------------------- !
! OPEN ASCII FILES !---------------------------------------- !
! ---------------------------------------------------------- !
Expand All @@ -338,13 +372,17 @@ SUBROUTINE initialise_ecogem( &
enddo

! get explicit grazing parameters from input file
if(ctrl_grazing_explicit)then
CALL sub_init_explicit_grazing_params()
if(ctrl_grazing_explicit .AND. .NOT. ctrl_use_foramecogenie)then
CALL sub_init_explicit_grazing_params()
else if (ctrl_grazing_explicit .AND. ctrl_use_foramecogenie) then
CALL sub_init_explicit_rich_grazing_params()
endif

if (ctrl_use_foramecogenie .AND. ctrl_debug_init > 0) call sub_debug_foramecogem()

! *** initialise plankton biomass array
call sub_init_plankton()

! JDW: allocate and load temperature forcing dataset
if(ctrl_force_T)then
allocate(T_input(n_i,n_j),STAT=alloc_error)
Expand Down
Loading