MODULE p4zfechem !!====================================================================== !! *** MODULE p4zfechem *** !! TOP : PISCES Compute iron chemistry and scavenging !!====================================================================== !! History : 3.5 ! 2012-07 (O. Aumont, A. Tagliabue, C. Ethe) Original code !! 3.6 ! 2015-05 (O. Aumont) PISCES quota !!---------------------------------------------------------------------- !! p4z_fechem : Compute remineralization/scavenging of iron !! p4z_fechem_init : Initialisation of parameters for remineralisation !! p4z_fechem_alloc : Allocate remineralisation variables !!---------------------------------------------------------------------- USE oce_trc ! shared variables between ocean and passive tracers USE trc ! passive tracers common variables USE sms_pisces ! PISCES Source Minus Sink variables USE p4zche ! chemical model USE p4zsbc ! Boundary conditions from sediments USE prtctl_trc ! print control for debugging USE iom ! I/O manager IMPLICIT NONE PRIVATE PUBLIC p4z_fechem ! called in p4zbio.F90 PUBLIC p4z_fechem_init ! called in trcsms_pisces.F90 LOGICAL :: ln_ligvar !: boolean for variable ligand concentration following Tagliabue and voelker REAL(wp), PUBLIC :: xlam1 !: scavenging rate of Iron REAL(wp), PUBLIC :: xlamdust !: scavenging rate of Iron by dust REAL(wp), PUBLIC :: ligand !: ligand concentration in the ocean REAL(wp), PUBLIC :: kfep !: rate constant for nanoparticle formation REAL(wp), PUBLIC :: scaveff !: Fraction of scavenged iron that is considered as being subject to solubilization !!---------------------------------------------------------------------- !! NEMO/TOP 4.0 , NEMO Consortium (2018) !! $Id$ !! Software governed by the CeCILL license (see ./LICENSE) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE p4z_fechem( kt, knt ) !!--------------------------------------------------------------------- !! *** ROUTINE p4z_fechem *** !! !! ** Purpose : Compute remineralization/scavenging of iron !! !! ** Method : A simple chemistry model of iron from Aumont and Bopp (2006) !! based on one ligand and one inorganic form !!--------------------------------------------------------------------- INTEGER, INTENT(in) :: kt, knt ! ocean time step ! INTEGER :: ji, jj, jk, jic, jn REAL(wp) :: zlam1a, zlam1b REAL(wp) :: zkeq, zfesatur, zfecoll, fe3sol, zligco REAL(wp) :: zscave, zaggdfea, zaggdfeb, ztrc, zdust, zklight REAL(wp) :: ztfe, zhplus, zxlam, zaggliga, zaggligb REAL(wp) :: zrfact2 CHARACTER (len=25) :: charout REAL(wp), DIMENSION(jpi,jpj,jpk) :: zTL1, zFe3, ztotlig, precip, precipno3, zFeL1 REAL(wp), DIMENSION(jpi,jpj,jpk) :: zcoll3d, zscav3d, zlcoll3d, zprecip3d !!--------------------------------------------------------------------- ! IF( ln_timing ) CALL timing_start('p4z_fechem') ! zFe3 (:,:,:) = 0. ; zFeL1(:,:,:) = 0. zTL1 (:,:,:) = 0. ! Total ligand concentration : Ligands can be chosen to be constant or variable ! Parameterization from Pham and Ito (2018) ! ------------------------------------------------- IF( ln_ligvar ) THEN ztotlig(:,:,:) = 0.09 * 0.667 * trb(:,:,:,jpdoc) * 1E6 + ligand * 1E9 + MAX(0., chemo2(:,:,:) - trb(:,:,:,jpoxy) ) / 400.E-6 ztotlig(:,:,:) = MIN( ztotlig(:,:,:), 10. ) ELSE IF( ln_ligand ) THEN ; ztotlig(:,:,:) = trb(:,:,:,jplgw) * 1E9 ELSE ; ztotlig(:,:,:) = ligand * 1E9 ENDIF ENDIF ! ------------------------------------------------------------ ! from Aumont and Bopp (2006) ! This model is based on one ligand, Fe2+ and Fe3+ ! Chemistry is supposed to be fast enough to be at equilibrium ! ------------------------------------------------------------ DO jk = 1, jpkm1 DO jj = 1, jpj DO ji = 1, jpi zTL1(ji,jj,jk) = ztotlig(ji,jj,jk) zkeq = fekeq(ji,jj,jk) zklight = 4.77E-7 * etot(ji,jj,jk) * 0.5 / 10**-6.3 zfesatur = zTL1(ji,jj,jk) * 1E-9 ztfe = (1.0 + zklight) * trb(ji,jj,jk,jpfer) ! Fe' is the root of a 2nd order polynom zFe3 (ji,jj,jk) = ( -( 1. + zfesatur * zkeq + zklight + consfe3(ji,jj,jk)/10**-6.3 - zkeq * trb(ji,jj,jk,jpfer) ) & & + SQRT( ( 1. + zfesatur * zkeq + zklight + consfe3(ji,jj,jk)/10**-6.3 - zkeq * trb(ji,jj,jk,jpfer) )**2 & & + 4. * ztfe * zkeq) ) / ( 2. * zkeq ) zFeL1(ji,jj,jk) = MAX( 0., trb(ji,jj,jk,jpfer) - zFe3(ji,jj,jk) ) END DO END DO END DO ! plig(:,:,:) = MAX( 0., ( zFeL1(:,:,:) / ( trb(:,:,:,jpfer) + rtrn ) ) ) ! zdust = 0. ! if no dust available DO jk = 1, jpkm1 DO jj = 1, jpj DO ji = 1, jpi ! Scavenging rate of iron. This scavenging rate depends on the load of particles of sea water. ! This parameterization assumes a simple second order kinetics (k[Particles][Fe]). ! Scavenging onto dust is also included as evidenced from the DUNE experiments. ! -------------------------------------------------------------------------------------- zhplus = max( rtrn, hi(ji,jj,jk) ) fe3sol = fesol(ji,jj,jk,1) * ( zhplus**3 + fesol(ji,jj,jk,2) * zhplus**2 & & + fesol(ji,jj,jk,3) * zhplus + fesol(ji,jj,jk,4) & & + fesol(ji,jj,jk,5) / zhplus ) ! zfecoll = 0.5 * zFeL1(ji,jj,jk) ! precipitation of Fe3+, creation of nanoparticles precip(ji,jj,jk) = MAX( 0., ( zFe3(ji,jj,jk) - fe3sol ) ) * kfep * xstep * ( 1.0 - nitrfac(ji,jj,jk) ) ! Precipitation of Fe2+ due to oxidation by NO3 (Croot et al., 2019) ! This occurs in anoxic waters only precipno3(ji,jj,jk) = 2.0 * 130.0 * trb(ji,jj,jk,jpno3) * nitrfac(ji,jj,jk) * xstep * zFe3(ji,jj,jk) ! ztrc = ( trb(ji,jj,jk,jppoc) + trb(ji,jj,jk,jpgoc) + trb(ji,jj,jk,jpcal) + trb(ji,jj,jk,jpgsi) ) * 1.e6 ztrc = MAX( rtrn, ztrc ) IF( ln_dust ) zdust = dust(ji,jj) / ( wdust / rday ) * tmask(ji,jj,jk) zxlam = MAX( 1.E-3, (1. - EXP(-2 * trb(ji,jj,jk,jpoxy) / 100.E-6 ) )) zlam1b = 3.e-5 + ( xlamdust * zdust + xlam1 * ztrc ) * zxlam zscave = zFe3(ji,jj,jk) * zlam1b * xstep ! Compute the coagulation of colloidal iron. This parameterization ! could be thought as an equivalent of colloidal pumping. ! It requires certainly some more work as it is very poorly constrained. ! ---------------------------------------------------------------- zlam1a = ( 12.0 * 0.3 * trb(ji,jj,jk,jpdoc) + 9.05 * trb(ji,jj,jk,jppoc) ) * xdiss(ji,jj,jk) & & + ( 2.49 * trb(ji,jj,jk,jppoc) ) & & + ( 127.8 * 0.3 * trb(ji,jj,jk,jpdoc) + 725.7 * trb(ji,jj,jk,jppoc) ) zaggdfea = zlam1a * xstep * zfecoll ! zlam1b = ( 1.94 * xdiss(ji,jj,jk) + 1.37 ) * trb(ji,jj,jk,jpgoc) zaggdfeb = zlam1b * xstep * zfecoll ! tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zscave - zaggdfea - zaggdfeb & & - precip(ji,jj,jk) - precipno3(ji,jj,jk) tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zscave * scaveff * trb(ji,jj,jk,jppoc) / ztrc tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zscave * scaveff * trb(ji,jj,jk,jpgoc) / ztrc ! Precipitated iron is supposed to be permanently lost. ! Scavenged iron is supposed to be released back to seawater ! when POM is solubilized. This is highly uncertain as probably ! a significant part of it may be rescavenged back onto ! the particles. An efficiency factor is applied that is read ! in the namelist. ! See for instance Tagliabue et al. (2019). ! Aggregated FeL is considered as biogenic Fe as it ! probably remains complexed when the particle is solubilized. ! ------------------------------------------------------------- tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zaggdfea tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zaggdfeb zscav3d(ji,jj,jk) = zscave zcoll3d(ji,jj,jk) = zaggdfea + zaggdfeb zprecip3d(ji,jj,jk) = precip(ji,jj,jk) + precipno3(ji,jj,jk) ! END DO END DO END DO ! ! Define the bioavailable fraction of iron ! ---------------------------------------- biron(:,:,:) = trb(:,:,:,jpfer) ! IF( ln_ligand ) THEN ! DO jk = 1, jpkm1 DO jj = 1, jpj DO ji = 1, jpi ! Coagulation of ligands due to various processes (Brownian, shear, diff. sedimentation ! Coefficients are taken from p4zagg ! ------------------------------------------------------------------------------------- zlam1a = ( 12.0 * 0.3 * trb(ji,jj,jk,jpdoc) + 9.05 * trb(ji,jj,jk,jppoc) ) * xdiss(ji,jj,jk) & & + ( 2.49 * trb(ji,jj,jk,jppoc) ) & & + ( 127.8 * 0.3 * trb(ji,jj,jk,jpdoc) + 725.7 * trb(ji,jj,jk,jppoc) ) ! zlam1b = ( 1.94 * xdiss(ji,jj,jk) + 1.37 ) * trb(ji,jj,jk,jpgoc) ! 50% of the ligands are supposed to be in the colloidal size fraction ! as for FeL zligco = 0.5 * trb(ji,jj,jk,jplgw) zaggliga = zlam1a * xstep * zligco zaggligb = zlam1b * xstep * zligco tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) - zaggliga - zaggligb zlcoll3d(ji,jj,jk) = zaggliga + zaggligb END DO END DO END DO ! ENDIF ! Output of some diagnostics variables ! --------------------------------- IF( lk_iomput .AND. knt == nrdttrc ) THEN zrfact2 = 1.e3 * rfact2r ! conversion from mol/L/timestep into mol/m3/s IF( iom_use("Fe3") ) CALL iom_put("Fe3" , zFe3 (:,:,:) * tmask(:,:,:) ) ! Fe3+ IF( iom_use("FeL1") ) CALL iom_put("FeL1" , zFeL1 (:,:,:) * tmask(:,:,:) ) ! FeL1 IF( iom_use("TL1") ) CALL iom_put("TL1" , zTL1 (:,:,:) * tmask(:,:,:) ) ! TL1 IF( iom_use("Totlig") ) CALL iom_put("Totlig" , ztotlig(:,:,:) * tmask(:,:,:) ) ! TL IF( iom_use("Biron") ) CALL iom_put("Biron" , biron (:,:,:) * 1e9 * tmask(:,:,:) ) ! biron IF( iom_use("FESCAV") ) CALL iom_put("FESCAV" , zscav3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) IF( iom_use("FECOLL") ) CALL iom_put("FECOLL" , zcoll3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) IF( iom_use("FEPREC") ) CALL iom_put("FEPREC" , zprecip3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) IF( iom_use("LGWCOLL")) CALL iom_put("LGWCOLL", zlcoll3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) ENDIF IF(ln_ctl) THEN ! print mean trends (used for debugging) WRITE(charout, FMT="('fechem')") CALL prt_ctl_trc_info(charout) CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) ENDIF ! IF( ln_timing ) CALL timing_stop('p4z_fechem') ! END SUBROUTINE p4z_fechem SUBROUTINE p4z_fechem_init !!---------------------------------------------------------------------- !! *** ROUTINE p4z_fechem_init *** !! !! ** Purpose : Initialization of iron chemistry parameters !! !! ** Method : Read the nampisfer namelist and check the parameters !! called at the first timestep !! !! ** input : Namelist nampisfer !! !!---------------------------------------------------------------------- INTEGER :: ios ! Local integer !! NAMELIST/nampisfer/ ln_ligvar, xlam1, xlamdust, ligand, kfep, scaveff !!---------------------------------------------------------------------- ! IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'p4z_rem_init : Initialization of iron chemistry parameters' WRITE(numout,*) '~~~~~~~~~~~~' ENDIF ! REWIND( numnatp_ref ) ! Namelist nampisfer in reference namelist : Pisces iron chemistry READ ( numnatp_ref, nampisfer, IOSTAT = ios, ERR = 901) 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisfer in reference namelist' ) REWIND( numnatp_cfg ) ! Namelist nampisfer in configuration namelist : Pisces iron chemistry READ ( numnatp_cfg, nampisfer, IOSTAT = ios, ERR = 902 ) 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'nampisfer in configuration namelist' ) IF(lwm) WRITE( numonp, nampisfer ) IF(lwp) THEN ! control print WRITE(numout,*) ' Namelist : nampisfer' WRITE(numout,*) ' variable concentration of ligand ln_ligvar =', ln_ligvar WRITE(numout,*) ' scavenging rate of Iron xlam1 =', xlam1 WRITE(numout,*) ' scavenging rate of Iron by dust xlamdust =', xlamdust WRITE(numout,*) ' ligand concentration in the ocean ligand =', ligand WRITE(numout,*) ' rate constant for nanoparticle formation kfep =', kfep WRITE(numout,*) ' Scavenged iron that is added to POFe scaveff =', scaveff ENDIF ! END SUBROUTINE p4z_fechem_init !!====================================================================== END MODULE p4zfechem