MODULE asmlogchlbal_hadocc !!====================================================================== !! *** MODULE asmlogchlbal_hadocc *** !! Calculate increments to HadOCC based on surface logchl increments !! !! IMPORTANT NOTE: This calls the bioanalysis routine of Hemmings et al. !! For licensing reasons this is kept in its own internal Met Office !! branch (dev/frdf/vn3.6_nitrogen_balancing) rather than in the Paris !! repository, and must be merged in when building. !! !!====================================================================== !! History : 3.6 ! 2017-08 (D. Ford) Adapted from bioanal.F90 !!---------------------------------------------------------------------- #if defined key_asminc && defined key_hadocc !!---------------------------------------------------------------------- !! 'key_asminc' : assimilation increment interface !! 'key_hadocc' : HadOCC model !!---------------------------------------------------------------------- !! asm_logchl_bal_hadocc : routine to calculate increments to HadOCC !!---------------------------------------------------------------------- USE par_kind, ONLY: wp ! kind parameters USE par_oce, ONLY: jpi, jpj, jpk ! domain array sizes USE dom_oce, ONLY: gdepw_n ! domain information USE zdfmxl ! mixed layer depth USE iom ! i/o USE par_hadocc ! HadOCC parameters USE had_bgc_stnd, ONLY: kmt ! HadOCC parameters USE had_bgc_const ! HadOCC parameters USE par_trc, ONLY: jptra ! Tracer parameters USE bioanalysis ! Nitrogen balancing IMPLICIT NONE PRIVATE PUBLIC asm_logchl_bal_hadocc ! Default values for biological assimilation parameters ! Should match Hemmings et al. (2008) REAL(wp), PARAMETER :: balnutext = 0.6 !: Default nutrient balancing factor REAL(wp), PARAMETER :: balnutmin = 0.1 !: Fraction of phytoplankton loss to nutrient REAL(wp), PARAMETER :: r = 1 !: Reliability of model specific growth rate REAL(wp), PARAMETER :: beta_g = 0.05 !: Low rate bias correction for growth rate estimator REAL(wp), PARAMETER :: beta_l = 0.05 !: Low rate bias correction for primary loss rate estimator REAL(wp), PARAMETER :: beta_m = 0.05 !: Low rate bias correction for secondary loss rate estimator REAL(wp), PARAMETER :: a_g = 0.2 !: Error s.d. for log10 of growth rate estimator REAL(wp), PARAMETER :: a_l = 0.4 !: Error s.d. for log10 of primary loss rate estimator REAL(wp), PARAMETER :: a_m = 0.7 !: Error s.d. for log10 of secondary loss rate estimator REAL(wp), PARAMETER :: zfracb0 = 0.7 !: Base zooplankton fraction of loss to Z & D REAL(wp), PARAMETER :: zfracb1 = 0 !: Phytoplankton sensitivity of zooplankton fraction REAL(wp), PARAMETER :: qrfmax = 1.1 !: Maximum nutrient limitation reduction factor REAL(wp), PARAMETER :: qafmax = 1.1 !: Maximum nutrient limitation amplification factor REAL(wp), PARAMETER :: zrfmax = 2 !: Maximum zooplankton reduction factor REAL(wp), PARAMETER :: zafmax = 2 !: Maximum zooplankton amplification factor REAL(wp), PARAMETER :: prfmax = 10 !: Maximum phytoplankton reduction factor (secondary) REAL(wp), PARAMETER :: incphymin = 0.0001 !: Minimum size of non-zero phytoplankton increment REAL(wp), PARAMETER :: integnstep = 20 !: Number of steps for p.d.f. integral evaluation REAL(wp), PARAMETER :: pthreshold = 0.01 !: Fractional threshold level for setting p.d.f. ! LOGICAL, PARAMETER :: diag_active = .TRUE. !: Depth-independent diagnostics LOGICAL, PARAMETER :: diag_fulldepth_active = .TRUE. !: Full-depth diagnostics LOGICAL, PARAMETER :: gl_active = .TRUE. !: Growth/loss-based balancing LOGICAL, PARAMETER :: nbal_active = .TRUE. !: Nitrogen balancing LOGICAL, PARAMETER :: subsurf_active = .TRUE. !: Increments below MLD LOGICAL, PARAMETER :: deepneg_active = .FALSE. !: Negative primary increments below MLD LOGICAL, PARAMETER :: deeppos_active = .FALSE. !: Positive primary increments below MLD LOGICAL, PARAMETER :: nutprof_active = .TRUE. !: Secondary increments CONTAINS SUBROUTINE asm_logchl_bal_hadocc( logchl_bkginc, aincper, mld_choice_bgc, & & k_maxchlinc, ld_logchlbal, & & pgrow_avg_bkg, ploss_avg_bkg, & & phyt_avg_bkg, mld_max_bkg, & & chl_bkg, cchl_p_bkg, & & tracer_bkg, logchl_balinc ) !!--------------------------------------------------------------------------- !! *** ROUTINE asm_logchl_bal_hadocc *** !! !! ** Purpose : calculate increments to HadOCC from logchl increments !! !! ** Method : convert logchl increments to chl increments !! call nitrogen balancing scheme !! !! ** Action : populate logchl_balinc !! !! References : Hemmings et al., 2008, J. Mar. Res. !! Ford et al., 2012, Ocean Sci. !!--------------------------------------------------------------------------- !! REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: logchl_bkginc ! logchl increments REAL(wp), INTENT(in ) :: aincper ! Assimilation period INTEGER, INTENT(in ) :: mld_choice_bgc ! MLD criterion REAL(wp), INTENT(in ) :: k_maxchlinc ! Max chl increment LOGICAL, INTENT(in ) :: ld_logchlbal ! Balancing y/n REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: pgrow_avg_bkg ! Avg phyto growth REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: ploss_avg_bkg ! Avg phyto loss REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: phyt_avg_bkg ! Avg phyto REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: mld_max_bkg ! Max MLD REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: chl_bkg ! Surface chlorophyll REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: cchl_p_bkg ! Surface C:Chl REAL(wp), INTENT(in ), DIMENSION(jpi,jpj,jpk,jptra) :: tracer_bkg ! State variables REAL(wp), INTENT( out), DIMENSION(jpi,jpj,jpk,jptra) :: logchl_balinc ! Balancing increments !! INTEGER :: ji, jj, jk, jn ! Loop counters INTEGER :: jkmax ! Loop index INTEGER, DIMENSION(6) :: i_tracer ! Tracer indices REAL(wp), DIMENSION(jpi,jpj) :: chl_inc ! Chlorophyll increments REAL(wp), DIMENSION(jpi,jpj) :: zmld ! Mixed layer depth REAL(wp), DIMENSION(16) :: modparm ! Model parameters REAL(wp), DIMENSION(20) :: assimparm ! Assimilation parameters REAL(wp), DIMENSION(jpi,jpj,jpk,6) :: bstate ! Background state REAL(wp), DIMENSION(jpi,jpj,jpk,6) :: outincs ! Balancing increments REAL(wp), DIMENSION(jpi,jpj,22) :: diag ! Depth-indep diagnostics REAL(wp), DIMENSION(jpi,jpj,jpk,22) :: diag_fulldepth ! Full-depth diagnostics !!--------------------------------------------------------------------------- ! Convert log10(chlorophyll) increment back to a chlorophyll increment ! In order to transform logchl incs to chl incs, need to account for model ! background, cannot simply do 10^logchl_bkginc. Need to: ! 1) Add logchl inc to log10(background) to get log10(analysis) ! 2) Take 10^log10(analysis) to get analysis ! 3) Subtract background from analysis to get chl incs ! If k_maxchlinc > 0 then cap total absolute chlorophyll increment at that value DO jj = 1, jpj DO ji = 1, jpi IF ( chl_bkg(ji,jj) > 0.0 ) THEN chl_inc(ji,jj) = 10**( LOG10( chl_bkg(ji,jj) ) + logchl_bkginc(ji,jj) ) - chl_bkg(ji,jj) IF ( k_maxchlinc > 0.0 ) THEN chl_inc(ji,jj) = MAX( -1.0 * k_maxchlinc, MIN( chl_inc(ji,jj), k_maxchlinc ) ) ENDIF ELSE chl_inc(ji,jj) = 0.0 ENDIF END DO END DO ! Select mixed layer SELECT CASE( mld_choice_bgc ) CASE ( 1 ) ! Turbocline/mixing depth [W points] zmld(:,:) = hmld(:,:) CASE ( 2 ) ! Density criterion (0.01 kg/m^3 change from 10m) [W points] zmld(:,:) = hmlp(:,:) CASE ( 3 ) ! Kara MLD [Interpolated] #if defined key_karaml IF ( ln_kara ) THEN zmld(:,:) = hmld_kara(:,:) ELSE CALL ctl_stop( ' Kara mixed layer requested for LogChl assimilation,', & & ' but ln_kara=.false.' ) ENDIF #else CALL ctl_stop( ' Kara mixed layer requested for LogChl assimilation,', & & ' but is not defined' ) #endif CASE ( 4 ) ! Temperature criterion (0.2 K change from surface) [T points] !zmld(:,:) = hmld_tref(:,:) CALL ctl_stop( ' hmld_tref mixed layer requested for LogChl assimilation,', & & ' but is not available in this version' ) CASE ( 5 ) ! Density criterion (0.01 kg/m^3 change from 10m) [T points] zmld(:,:) = hmlpt(:,:) END SELECT IF ( ld_logchlbal ) THEN ! Nitrogen balancing ! Set up model parameters to be passed into Hemmings balancing routine modparm(1) = grow_sat modparm(2) = psmax modparm(3) = par modparm(4) = alpha modparm(5) = resp_rate modparm(6) = pmort_rate modparm(7) = phyto_min modparm(8) = z_mort_1 modparm(9) = z_mort_2 modparm(10) = c2n_p modparm(11) = c2n_z modparm(12) = c2n_d modparm(13) = graze_threshold modparm(14) = holling_coef modparm(15) = graze_sat modparm(16) = graze_max ! Set up assimilation parameters to be passed into balancing routine ! Not sure what assimparm(1) is meant to be, but it doesn't get used assimparm(2) = balnutext assimparm(3) = balnutmin assimparm(4) = r assimparm(5) = beta_g assimparm(6) = beta_l assimparm(7) = beta_m assimparm(8) = a_g assimparm(9) = a_l assimparm(10) = a_m assimparm(11) = zfracb0 assimparm(12) = zfracb1 assimparm(13) = qrfmax assimparm(14) = qafmax assimparm(15) = zrfmax assimparm(16) = zafmax assimparm(17) = prfmax assimparm(18) = incphymin assimparm(19) = integnstep assimparm(20) = pthreshold ! Set up external tracer indices array bstate i_tracer(1) = 1 ! nutrient i_tracer(2) = 2 ! phytoplankton i_tracer(3) = 3 ! zooplankton i_tracer(4) = 4 ! detritus i_tracer(5) = 5 ! DIC i_tracer(6) = 6 ! Alkalinity ! Set background state bstate(:,:,:,i_tracer(1)) = tracer_bkg(:,:,:,jp_had_nut) bstate(:,:,:,i_tracer(2)) = tracer_bkg(:,:,:,jp_had_phy) bstate(:,:,:,i_tracer(3)) = tracer_bkg(:,:,:,jp_had_zoo) bstate(:,:,:,i_tracer(4)) = tracer_bkg(:,:,:,jp_had_pdn) bstate(:,:,:,i_tracer(5)) = tracer_bkg(:,:,:,jp_had_dic) bstate(:,:,:,i_tracer(6)) = tracer_bkg(:,:,:,jp_had_alk) ! Call nitrogen balancing routine CALL bio_analysis( jpi, jpj, jpk, ZDZ(:,:,:), i_tracer, modparm, & & n2be_p, n2be_z, n2be_d, assimparm, & & INT(aincper), 1, kmt(:,:), tmask(:,:,:), & & zmld(:,:), mld_max_bkg(:,:), chl_inc(:,:), cchl_p_bkg(:,:), & & nbal_active, phyt_avg_bkg(:,:), & & gl_active, pgrow_avg_bkg(:,:), ploss_avg_bkg(:,:), & & subsurf_active, deepneg_active, & & deeppos_active, nutprof_active, & & bstate, outincs, & & diag_active, diag, & & diag_fulldepth_active, diag_fulldepth ) ! Save balancing increments logchl_balinc(:,:,:,jp_had_nut) = outincs(:,:,:,i_tracer(1)) logchl_balinc(:,:,:,jp_had_phy) = outincs(:,:,:,i_tracer(2)) logchl_balinc(:,:,:,jp_had_zoo) = outincs(:,:,:,i_tracer(3)) logchl_balinc(:,:,:,jp_had_pdn) = outincs(:,:,:,i_tracer(4)) logchl_balinc(:,:,:,jp_had_dic) = outincs(:,:,:,i_tracer(5)) logchl_balinc(:,:,:,jp_had_alk) = outincs(:,:,:,i_tracer(6)) ELSE ! No nitrogen balancing ! Initialise phytoplankton increment to zero logchl_balinc(:,:,:,jp_had_phy) = 0.0 ! Convert surface chlorophyll increment to phytoplankton nitrogen logchl_balinc(:,:,1,jp_had_phy) = ( cchl_p_bkg(:,:) / (mw_carbon * c2n_p) ) * chl_inc(:,:) ! Propagate through mixed layer DO jj = 1, jpj DO ji = 1, jpi ! jkmax = jpk-1 DO jk = jpk-1, 1, -1 IF ( ( zmld(ji,jj) > gdepw_n(ji,jj,jk) ) .AND. & & ( zmld(ji,jj) <= gdepw_n(ji,jj,jk+1) ) ) THEN zmld(ji,jj) = gdepw_n(ji,jj,jk+1) jkmax = jk ENDIF END DO ! DO jk = 2, jkmax logchl_balinc(ji,jj,jk,jp_had_phy) = logchl_balinc(ji,jj,1,jp_had_phy) END DO ! END DO END DO ! Set other balancing increments to zero logchl_balinc(:,:,:,jp_had_nut) = 0.0 logchl_balinc(:,:,:,jp_had_zoo) = 0.0 logchl_balinc(:,:,:,jp_had_pdn) = 0.0 logchl_balinc(:,:,:,jp_had_dic) = 0.0 logchl_balinc(:,:,:,jp_had_alk) = 0.0 ENDIF END SUBROUTINE asm_logchl_bal_hadocc #else !!---------------------------------------------------------------------- !! Default option : Empty routine !!---------------------------------------------------------------------- CONTAINS SUBROUTINE asm_logchl_bal_hadocc( logchl_bkginc, aincper, mld_choice_bgc, & & k_maxchlinc, ld_logchlbal, & & pgrow_avg_bkg, ploss_avg_bkg, & & phyt_avg_bkg, mld_max_bkg, & & chl_bkg, cchl_p_bkg, & & tracer_bkg, logchl_balinc ) REAL :: logchl_bkginc(:,:) REAL :: aincper INTEGER :: mld_choice_bgc REAL :: k_maxchlinc LOGICAL :: ld_logchlbal REAL :: pgrow_avg_bkg(:,:) REAL :: ploss_avg_bkg(:,:) REAL :: phyt_avg_bkg(:,:) REAL :: mld_max_bkg(:,:) REAL :: chl_bkg(:,:) REAL :: cchl_p_bkg(:,:) REAL :: tracer_bkg(:,:,:,:) REAL :: logchl_balinc(:,:,:,:) WRITE(*,*) 'asm_logchl_bal_hadocc: You should not have seen this print! error?' END SUBROUTINE asm_logchl_bal_hadocc #endif !!====================================================================== END MODULE asmlogchlbal_hadocc