New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
p4zfechem.F90 in NEMO/trunk/src/TOP/PISCES/P4Z – NEMO

source: NEMO/trunk/src/TOP/PISCES/P4Z/p4zfechem.F90

Last change on this file was 15459, checked in by cetlod, 3 years ago

Various bug fixes and more comments in PISCES routines ; sette test OK in debug mode, nn_hls=1/2, with tiling ; run.stat unchanged ; of course tracer.stat different

  • Property svn:keywords set to Id
File size: 14.0 KB
RevLine 
[3443]1MODULE p4zfechem
2   !!======================================================================
3   !!                         ***  MODULE p4zfechem  ***
4   !! TOP :   PISCES Compute iron chemistry and scavenging
5   !!======================================================================
[3461]6   !! History :   3.5  !  2012-07 (O. Aumont, A. Tagliabue, C. Ethe) Original code
[7646]7   !!             3.6  !  2015-05  (O. Aumont) PISCES quota
[3443]8   !!----------------------------------------------------------------------
[9169]9   !!   p4z_fechem       : Compute remineralization/scavenging of iron
10   !!   p4z_fechem_init  : Initialisation of parameters for remineralisation
11   !!   p4z_fechem_alloc : Allocate remineralisation variables
[3443]12   !!----------------------------------------------------------------------
[9169]13   USE oce_trc         ! shared variables between ocean and passive tracers
14   USE trc             ! passive tracers common variables
15   USE sms_pisces      ! PISCES Source Minus Sink variables
16   USE p4zche          ! chemical model
[12377]17   USE p4zbc           ! Boundary conditions from sediments
[13286]18   USE prtctl          ! print control for debugging
[9169]19   USE iom             ! I/O manager
[3443]20
21   IMPLICIT NONE
22   PRIVATE
23
[9169]24   PUBLIC   p4z_fechem        ! called in p4zbio.F90
25   PUBLIC   p4z_fechem_init   ! called in trcsms_pisces.F90
[3443]26
[9169]27   LOGICAL          ::   ln_ligvar    !: boolean for variable ligand concentration following Tagliabue and voelker
28   REAL(wp), PUBLIC ::   xlam1        !: scavenging rate of Iron
29   REAL(wp), PUBLIC ::   xlamdust     !: scavenging rate of Iron by dust
30   REAL(wp), PUBLIC ::   ligand       !: ligand concentration in the ocean
31   REAL(wp), PUBLIC ::   kfep         !: rate constant for nanoparticle formation
[15459]32   REAL(wp), PUBLIC ::   scaveff      !: Fraction of scavenged iron that is considered as being subject to solubilization
[3443]33
[12377]34   !! * Substitutions
35#  include "do_loop_substitute.h90"
[13237]36#  include "domzgr_substitute.h90"
[3443]37   !!----------------------------------------------------------------------
[10067]38   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[10069]39   !! $Id$
[10068]40   !! Software governed by the CeCILL license (see ./LICENSE)
[3443]41   !!----------------------------------------------------------------------
42CONTAINS
43
[12377]44   SUBROUTINE p4z_fechem( kt, knt, Kbb, Kmm, Krhs )
[3443]45      !!---------------------------------------------------------------------
46      !!                     ***  ROUTINE p4z_fechem  ***
47      !!
48      !! ** Purpose :   Compute remineralization/scavenging of iron
49      !!
[10401]50      !! ** Method  :   A simple chemistry model of iron from Aumont and Bopp (2006)
51      !!                based on one ligand and one inorganic form
[3443]52      !!---------------------------------------------------------------------
[9169]53      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step
[12377]54      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level indices
[3443]55      !
[7646]56      INTEGER  ::   ji, jj, jk, jic, jn
[15459]57      REAL(wp) ::   zlam1a, zlam1b
58      REAL(wp) ::   zkeq, zfesatur, fe3sol, zligco
59      REAL(wp) ::   zscave, zaggdfea, zaggdfeb, ztrc, zdust, zklight
60      REAL(wp) ::   ztfe, zhplus, zxlam, zaggliga, zaggligb
61      REAL(wp) ::   zprecip, zprecipno3,  zconsfe, za1
62      REAL(wp) ::   zrfact2
[7646]63      CHARACTER (len=25) :: charout
[15459]64      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zTL1, zFe3, ztotlig, zfeprecip, zFeL1, zfecoll
[10362]65      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zcoll3d, zscav3d, zlcoll3d
[3443]66      !!---------------------------------------------------------------------
67      !
[9124]68      IF( ln_timing )   CALL timing_start('p4z_fechem')
[3443]69      !
[15459]70      zFe3     (:,:,jpk) = 0.
71      zFeL1    (:,:,jpk) = 0.
72      zTL1     (:,:,jpk) = 0.
73      zfeprecip(:,:,jpk) = 0.
74      zcoll3d  (:,:,jpk) = 0.
75      zscav3d  (:,:,jpk) = 0.
76      zlcoll3d (:,:,jpk) = 0.
77      zfecoll  (:,:,jpk) = 0.
78      xfecolagg(:,:,jpk) = 0.
79      xcoagfe  (:,:,jpk) = 0.
80      !
[3443]81      ! Total ligand concentration : Ligands can be chosen to be constant or variable
[15459]82      ! Parameterization from Pham and Ito (2018)
[3443]83      ! -------------------------------------------------
[15459]84      xfecolagg(:,:,:) = ligand * 1E9 + MAX(0., chemo2(:,:,:) - tr(:,:,:,jpoxy,Kbb) ) / 400.E-6
[3443]85      IF( ln_ligvar ) THEN
[15459]86         ztotlig(:,:,:) =  0.09 * 0.667 * tr(:,:,:,jpdoc,Kbb) * 1E6 + xfecolagg(:,:,:)
[7753]87         ztotlig(:,:,:) =  MIN( ztotlig(:,:,:), 10. )
[3443]88      ELSE
[12377]89        IF( ln_ligand ) THEN  ;   ztotlig(:,:,:) = tr(:,:,:,jplgw,Kbb) * 1E9
[15459]90        ELSE                  ;   ztotlig(:,:,:) = ligand * 1E9 
[7646]91        ENDIF
[3443]92      ENDIF
93
[10401]94      ! ------------------------------------------------------------
95      !  from Aumont and Bopp (2006)
[15459]96      ! This model is based on one ligand, Fe2+ and Fe3+
[10401]97      ! Chemistry is supposed to be fast enough to be at equilibrium
98      ! ------------------------------------------------------------
[15090]99      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1)
[15459]100          zTL1(ji,jj,jk)  = ztotlig(ji,jj,jk)
101          zkeq            = fekeq(ji,jj,jk)
102          zklight         = 4.77E-7 * etot(ji,jj,jk) * 0.5 / ( 10**(-6.3) )
103          zconsfe         = consfe3(ji,jj,jk) / ( 10**(-6.3) )
104          zfesatur        = zTL1(ji,jj,jk) * 1E-9
105          ztfe            = (1.0 + zklight) * tr(ji,jj,jk,jpfer,Kbb) 
106          ! Fe' is the root of a 2nd order polynom
107          za1 =  1. + zfesatur * zkeq + zklight +  zconsfe - zkeq * tr(ji,jj,jk,jpfer,Kbb)
108          zFe3 (ji,jj,jk) = ( -1 * za1 + SQRT( za1**2 + 4. * ztfe * zkeq) ) / ( 2. * zkeq + rtrn )
109          zFeL1(ji,jj,jk) = MAX( 0., tr(ji,jj,jk,jpfer,Kbb) - zFe3(ji,jj,jk) )
[12377]110      END_3D
[15459]111      !
112      plig(:,:,:) =  MAX( 0., ( zFeL1(:,:,:) / ( tr(:,:,:,jpfer,Kbb) + rtrn ) ) )
113      !
114      zdust = 0.         ! if no dust available
[7646]115
[15459]116      ! Computation of the colloidal fraction that is subjecto to coagulation
117      ! The assumption is that 50% of complexed iron is colloidal. Furthermore
118      ! The refractory part is supposed to be non sticky. The refractory
119      ! fraction is supposed to equal to the background concentration +
120      ! the fraction that accumulates in the deep ocean. AOU is taken as a
121      ! proxy of that accumulation following numerous studies showing
122      ! some relationship between weak ligands and AOU.
123      ! An issue with that parameterization is that when ligands are not
124      ! prognostic or non variable, all the colloidal fraction is supposed
125      ! to coagulate
126      ! ----------------------------------------------------------------------
127      IF (ln_ligand) THEN
128         zfecoll(:,:,:) = 0.5 * zFeL1(:,:,:) * MAX(0., tr(:,:,:,jplgw,Kbb) - xfecolagg(:,:,:) * 1.0E-9 ) / ( tr(:,:,:,jplgw,Kbb) + rtrn ) 
129      ELSE
130         IF (ln_ligvar) THEN
131            zfecoll(:,:,:) = 0.5 * zFeL1(:,:,:) * MAX(0., tr(:,:,:,jplgw,Kbb) - xfecolagg(:,:,:) * 1.0E-9 ) / ( tr(:,:,:,jplgw,Kbb) + rtrn )   
132         ELSE
133            zfecoll(:,:,:) = 0.5 * zFeL1(:,:,:)
134         ENDIF
135      ENDIF
136
[15090]137      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1)
[12377]138         ! Scavenging rate of iron. This scavenging rate depends on the load of particles of sea water.
139         ! This parameterization assumes a simple second order kinetics (k[Particles][Fe]).
140         ! Scavenging onto dust is also included as evidenced from the DUNE experiments.
141         ! --------------------------------------------------------------------------------------
142         zhplus  = max( rtrn, hi(ji,jj,jk) )
143         fe3sol  = fesol(ji,jj,jk,1) * ( zhplus**3 + fesol(ji,jj,jk,2) * zhplus**2  &
144         &         + fesol(ji,jj,jk,3) * zhplus + fesol(ji,jj,jk,4)     &
145         &         + fesol(ji,jj,jk,5) / zhplus )
146         !
147         ! precipitation of Fe3+, creation of nanoparticles
[15459]148         zprecip = MAX( 0., ( zFe3(ji,jj,jk) - fe3sol ) ) * kfep * xstep * ( 1.0 - nitrfac(ji,jj,jk) ) 
149         ! Precipitation of Fe2+ due to oxidation by NO3 (Croot et al., 2019)
150         ! This occurs in anoxic waters only
151         zprecipno3 = 2.0 * 130.0 * tr(ji,jj,jk,jpno3,Kbb) * nitrfac(ji,jj,jk) * xstep * zFe3(ji,jj,jk)
[12377]152         !
[15459]153         zfeprecip(ji,jj,jk) = zprecip + zprecipno3
154         !
[12377]155         ztrc   = ( tr(ji,jj,jk,jppoc,Kbb) + tr(ji,jj,jk,jpgoc,Kbb) + tr(ji,jj,jk,jpcal,Kbb) + tr(ji,jj,jk,jpgsi,Kbb) ) * 1.e6 
[15459]156         ztrc = MAX( rtrn, ztrc )
157         IF( ll_dust )  zdust  = dust(ji,jj) / ( wdust / rday ) * tmask(ji,jj,jk)
158         zxlam  = MAX( 1.E-3, (1. - EXP(-2 * tr(ji,jj,jk,jpoxy,Kbb) / 100.E-6 ) ))
159         zlam1b = 3.e-5 + ( xlamdust * zdust + xlam1 * ztrc ) * zxlam
160         zscave = zFe3(ji,jj,jk) * zlam1b * xstep
[3443]161
[12377]162         !  Compute the coagulation of colloidal iron. This parameterization
163         !  could be thought as an equivalent of colloidal pumping.
164         !  It requires certainly some more work as it is very poorly constrained.
165         !  ----------------------------------------------------------------
[15459]166         zlam1a   = ( 12.0  * 0.3 * tr(ji,jj,jk,jpdoc,Kbb) + 9.05  * tr(ji,jj,jk,jppoc,Kbb) ) * xdiss(ji,jj,jk)    &
167             &    + ( 2.49  * tr(ji,jj,jk,jppoc,Kbb) )     &
168             &    + ( 127.8 * 0.3 * tr(ji,jj,jk,jpdoc,Kbb) + 725.7 * tr(ji,jj,jk,jppoc,Kbb) )
169         zaggdfea = zlam1a * xstep * zfecoll(ji,jj,jk)
170               !
171         zlam1b   = ( 1.94 * xdiss(ji,jj,jk) + 1.37 ) * tr(ji,jj,jk,jpgoc,Kbb)
172         zaggdfeb = zlam1b * xstep * zfecoll(ji,jj,jk)
173         xcoagfe(ji,jj,jk) = zlam1a + zlam1b
[12377]174         !
175         tr(ji,jj,jk,jpfer,Krhs) = tr(ji,jj,jk,jpfer,Krhs) - zscave - zaggdfea - zaggdfeb &
[15459]176         &                       - zfeprecip(ji,jj,jk)
177
178         tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + zscave * scaveff * tr(ji,jj,jk,jppoc,Kbb) / ztrc
179         tr(ji,jj,jk,jpbfe,Krhs) = tr(ji,jj,jk,jpbfe,Krhs) + zscave * scaveff * tr(ji,jj,jk,jppoc,Kbb) / ztrc
180
181
182          ! Precipitated iron is supposed to be permanently lost.
183          ! Scavenged iron is supposed to be released back to seawater
184          ! when POM is solubilized. This is highly uncertain as probably
185          ! a significant part of it may be rescavenged back onto
186          ! the particles. An efficiency factor is applied that is read
187          ! in the namelist.
188          ! See for instance Tagliabue et al. (2019).
189          ! Aggregated FeL is considered as biogenic Fe as it
190          ! probably remains  complexed when the particle is solubilized.
191          ! -------------------------------------------------------------
192          tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + zaggdfea
193          tr(ji,jj,jk,jpbfe,Krhs) = tr(ji,jj,jk,jpbfe,Krhs) + zaggdfeb
194          !
195          zscav3d(ji,jj,jk)   = zscave 
196          zcoll3d(ji,jj,jk)   = zaggdfea + zaggdfeb
[12377]197         !
198      END_3D
[3443]199      !
[3446]200      !  Define the bioavailable fraction of iron
201      !  ----------------------------------------
[12377]202      biron(:,:,:) = tr(:,:,:,jpfer,Kbb) 
[7646]203      !
[3443]204      !  Output of some diagnostics variables
205      !     ---------------------------------
[15459]206      IF( lk_iomput .AND. knt == nrdttrc ) THEN
207         zrfact2 = 1.e3 * rfact2r  ! conversion from mol/L/timestep into mol/m3/s
208         IF( iom_use("Fe3")    )  CALL iom_put("Fe3"    , zFe3   (:,:,:)       * tmask(:,:,:) )   ! Fe3+
209         IF( iom_use("FeL1")   )  CALL iom_put("FeL1"   , zFeL1  (:,:,:)       * tmask(:,:,:) )   ! FeL1
210         IF( iom_use("TL1")    )  CALL iom_put("TL1"    , zTL1   (:,:,:)       * tmask(:,:,:) )   ! TL1
211         IF( iom_use("Totlig") )  CALL iom_put("Totlig" , ztotlig(:,:,:)       * tmask(:,:,:) )   ! TL
212         IF( iom_use("Biron")  )  CALL iom_put("Biron"  , biron  (:,:,:)  * 1e9 * tmask(:,:,:) )   ! biron
213         IF( iom_use("FESCAV") )  CALL iom_put("FESCAV" , zscav3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 )
214         IF( iom_use("FECOLL") )  CALL iom_put("FECOLL" , zcoll3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 )
215         IF( iom_use("FEPREC") )  CALL iom_put("FEPREC" , zfeprecip(:,:,:) *1e9*tmask(:,:,:)*zrfact2 )
[3443]216      ENDIF
217
[12377]218      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
[3449]219         WRITE(charout, FMT="('fechem')")
[13286]220         CALL prt_ctl_info( charout, cdcomp = 'top' )
221         CALL prt_ctl(tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm)
[3443]222      ENDIF
223      !
[9124]224      IF( ln_timing )   CALL timing_stop('p4z_fechem')
[3443]225      !
226   END SUBROUTINE p4z_fechem
227
228
229   SUBROUTINE p4z_fechem_init
230      !!----------------------------------------------------------------------
231      !!                  ***  ROUTINE p4z_fechem_init  ***
232      !!
233      !! ** Purpose :   Initialization of iron chemistry parameters
234      !!
235      !! ** Method  :   Read the nampisfer namelist and check the parameters
236      !!      called at the first timestep
237      !!
238      !! ** input   :   Namelist nampisfer
239      !!
240      !!----------------------------------------------------------------------
[9124]241      INTEGER ::   ios   ! Local integer
242      !!
[15459]243      NAMELIST/nampisfer/ ln_ligvar, xlam1, xlamdust, ligand, kfep, scaveff 
[9124]244      !!----------------------------------------------------------------------
[9169]245      !
246      IF(lwp) THEN
247         WRITE(numout,*)
248         WRITE(numout,*) 'p4z_rem_init : Initialization of iron chemistry parameters'
249         WRITE(numout,*) '~~~~~~~~~~~~'
250      ENDIF
251      !
[4147]252      READ  ( numnatp_ref, nampisfer, IOSTAT = ios, ERR = 901)
[11536]253901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisfer in reference namelist' )
[4147]254      READ  ( numnatp_cfg, nampisfer, IOSTAT = ios, ERR = 902 )
[11536]255902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisfer in configuration namelist' )
[9169]256      IF(lwm) WRITE( numonp, nampisfer )
[4147]257
[9169]258      IF(lwp) THEN                     ! control print
259         WRITE(numout,*) '   Namelist : nampisfer'
260         WRITE(numout,*) '      variable concentration of ligand          ln_ligvar    =', ln_ligvar
261         WRITE(numout,*) '      scavenging rate of Iron                   xlam1        =', xlam1
262         WRITE(numout,*) '      scavenging rate of Iron by dust           xlamdust     =', xlamdust
263         WRITE(numout,*) '      ligand concentration in the ocean         ligand       =', ligand
264         WRITE(numout,*) '      rate constant for nanoparticle formation  kfep         =', kfep
[15459]265         WRITE(numout,*) '      Scavenged iron that is added to POFe      scaveff      =', scaveff
[3443]266      ENDIF
[15459]267      !
[3443]268   END SUBROUTINE p4z_fechem_init
[9124]269   
[3443]270   !!======================================================================
271END MODULE p4zfechem
Note: See TracBrowser for help on using the repository browser.