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/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/PISCES/P4Z/p4zfechem.F90 @ 13906

Last change on this file since 13906 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

  • Property svn:keywords set to Id
File size: 13.6 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
17   USE p4zsbc          ! Boundary conditions from sediments
18   USE prtctl_trc      ! print control for debugging
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
[3443]32
33   !!----------------------------------------------------------------------
[10067]34   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[10069]35   !! $Id$
[10068]36   !! Software governed by the CeCILL license (see ./LICENSE)
[3443]37   !!----------------------------------------------------------------------
38CONTAINS
39
[5385]40   SUBROUTINE p4z_fechem( kt, knt )
[3443]41      !!---------------------------------------------------------------------
42      !!                     ***  ROUTINE p4z_fechem  ***
43      !!
44      !! ** Purpose :   Compute remineralization/scavenging of iron
45      !!
[10401]46      !! ** Method  :   A simple chemistry model of iron from Aumont and Bopp (2006)
47      !!                based on one ligand and one inorganic form
[3443]48      !!---------------------------------------------------------------------
[9169]49      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step
[3443]50      !
[7646]51      INTEGER  ::   ji, jj, jk, jic, jn
[3446]52      REAL(wp) ::   zdep, zlam1a, zlam1b, zlamfac
[7646]53      REAL(wp) ::   zkeq, zfeequi, zfesatur, zfecoll, fe3sol
[3446]54      REAL(wp) ::   zdenom1, zscave, zaggdfea, zaggdfeb, zcoag
[3443]55      REAL(wp) ::   ztrc, zdust
[7646]56      REAL(wp) ::   zdenom2
57      REAL(wp) ::   zzFeL1, zzFeL2, zzFe2, zzFeP, zzFe3, zzstrn2
58      REAL(wp) ::   zrum, zcodel, zargu, zlight
[9169]59      REAL(wp) ::   zkox, zkph1, zkph2, zph, zionic, ztligand
60      REAL(wp) ::   za, zb, zc, zkappa1, zkappa2, za0, za1, za2
61      REAL(wp) ::   zxs, zfunc, zp, zq, zd, zr, zphi, zfff, zp3, zq2
[10362]62      REAL(wp) ::   ztfe, zoxy, zhplus, zxlam
[9169]63      REAL(wp) ::   zaggliga, zaggligb
64      REAL(wp) ::   dissol, zligco
[10362]65      REAL(wp) :: zrfact2
[7646]66      CHARACTER (len=25) :: charout
[9169]67      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zTL1, zFe3, ztotlig, precip, zFeL1
[10362]68      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zcoll3d, zscav3d, zlcoll3d
[3443]69      !!---------------------------------------------------------------------
70      !
[9124]71      IF( ln_timing )   CALL timing_start('p4z_fechem')
[3443]72      !
[7753]73      zFe3 (:,:,:) = 0.
74      zFeL1(:,:,:) = 0.
75      zTL1 (:,:,:) = 0.
[3461]76
[3443]77      ! Total ligand concentration : Ligands can be chosen to be constant or variable
78      ! Parameterization from Tagliabue and Voelker (2011)
79      ! -------------------------------------------------
80      IF( ln_ligvar ) THEN
[7753]81         ztotlig(:,:,:) =  0.09 * trb(:,:,:,jpdoc) * 1E6 + ligand * 1E9
82         ztotlig(:,:,:) =  MIN( ztotlig(:,:,:), 10. )
[3443]83      ELSE
[7753]84        IF( ln_ligand ) THEN  ;   ztotlig(:,:,:) = trb(:,:,:,jplgw) * 1E9
85        ELSE                  ;   ztotlig(:,:,:) = ligand * 1E9
[7646]86        ENDIF
[3443]87      ENDIF
88
[10401]89      ! ------------------------------------------------------------
90      !  from Aumont and Bopp (2006)
91      ! This model is based on one ligand and Fe'
92      ! Chemistry is supposed to be fast enough to be at equilibrium
93      ! ------------------------------------------------------------
94      DO jk = 1, jpkm1
[7646]95         DO jj = 1, jpj
96            DO ji = 1, jpi
[10401]97               zTL1(ji,jj,jk)  = ztotlig(ji,jj,jk)
98               zkeq            = fekeq(ji,jj,jk)
99               zfesatur        = zTL1(ji,jj,jk) * 1E-9
100               ztfe            = trb(ji,jj,jk,jpfer) 
101               ! Fe' is the root of a 2nd order polynom
102               zFe3 (ji,jj,jk) = ( -( 1. + zfesatur * zkeq - zkeq * ztfe )               &
103                  &              + SQRT( ( 1. + zfesatur * zkeq - zkeq * ztfe )**2       &
104                  &              + 4. * ztfe * zkeq) ) / ( 2. * zkeq )
105               zFe3 (ji,jj,jk) = zFe3(ji,jj,jk) * 1E9
106               zFeL1(ji,jj,jk) = MAX( 0., trb(ji,jj,jk,jpfer) * 1E9 - zFe3(ji,jj,jk) )
107           END DO
[7646]108         END DO
[10401]109      END DO
[3443]110         !
[7646]111
[3531]112      zdust = 0.         ! if no dust available
[3443]113      DO jk = 1, jpkm1
114         DO jj = 1, jpj
115            DO ji = 1, jpi
116               ! Scavenging rate of iron. This scavenging rate depends on the load of particles of sea water.
117               ! This parameterization assumes a simple second order kinetics (k[Particles][Fe]).
118               ! Scavenging onto dust is also included as evidenced from the DUNE experiments.
119               ! --------------------------------------------------------------------------------------
[10362]120               zhplus  = max( rtrn, hi(ji,jj,jk) )
121               fe3sol  = fesol(ji,jj,jk,1) * ( zhplus**3 + fesol(ji,jj,jk,2) * zhplus**2  &
122               &         + fesol(ji,jj,jk,3) * zhplus + fesol(ji,jj,jk,4)     &
123               &         + fesol(ji,jj,jk,5) / zhplus )
[10401]124               !
125               zfeequi = zFe3(ji,jj,jk) * 1E-9
126               zhplus  = max( rtrn, hi(ji,jj,jk) )
127               fe3sol  = fesol(ji,jj,jk,1) * ( zhplus**3 + fesol(ji,jj,jk,2) * zhplus**2  &
[10362]128                  &         + fesol(ji,jj,jk,3) * zhplus + fesol(ji,jj,jk,4)     &
129                  &         + fesol(ji,jj,jk,5) / zhplus )
[10401]130               zfecoll = 0.5 * zFeL1(ji,jj,jk) * 1E-9
131               ! precipitation of Fe3+, creation of nanoparticles
132               precip(ji,jj,jk) = MAX( 0., ( zFe3(ji,jj,jk) * 1E-9 - fe3sol ) ) * kfep * xstep
[7646]133               !
[5385]134               ztrc   = ( trb(ji,jj,jk,jppoc) + trb(ji,jj,jk,jpgoc) + trb(ji,jj,jk,jpcal) + trb(ji,jj,jk,jpgsi) ) * 1.e6 
[10362]135               IF( ln_dust )  zdust  = dust(ji,jj) / ( wdust / rday ) * tmask(ji,jj,jk) &
136               &  * EXP( -gdept_n(ji,jj,jk) / 540. )
137               IF (ln_ligand) THEN
138                  zxlam  = xlam1 * MAX( 1.E-3, EXP(-2 * etot(ji,jj,jk) / 10. ) * (1. - EXP(-2 * trb(ji,jj,jk,jpoxy) / 100.E-6 ) ))
139               ELSE
140                  zxlam  = xlam1 * 1.0
141               ENDIF
142               zlam1b = 3.e-5 + xlamdust * zdust + zxlam * ztrc
[7646]143               zscave = zfeequi * zlam1b * xstep
[3443]144
145               ! Compute the different ratios for scavenging of iron
146               ! to later allocate scavenged iron to the different organic pools
147               ! ---------------------------------------------------------
[10362]148               zdenom1 = zxlam * trb(ji,jj,jk,jppoc) / zlam1b
149               zdenom2 = zxlam * trb(ji,jj,jk,jpgoc) / zlam1b
[3443]150
151               !  Increased scavenging for very high iron concentrations found near the coasts
152               !  due to increased lithogenic particles and let say it is unknown processes (precipitation, ...)
153               !  -----------------------------------------------------------
[3475]154               zlamfac = MAX( 0.e0, ( gphit(ji,jj) + 55.) / 30. )
155               zlamfac = MIN( 1.  , zlamfac )
[6140]156               zdep    = MIN( 1., 1000. / gdept_n(ji,jj,jk) )
[10362]157               zcoag   = 1E-4 * ( 1. - zlamfac ) * zdep * xstep * trb(ji,jj,jk,jpfer)
[3443]158
159               !  Compute the coagulation of colloidal iron. This parameterization
160               !  could be thought as an equivalent of colloidal pumping.
161               !  It requires certainly some more work as it is very poorly constrained.
162               !  ----------------------------------------------------------------
[10362]163               zlam1a   = ( 0.369  * 0.3 * trb(ji,jj,jk,jpdoc) + 102.4  * trb(ji,jj,jk,jppoc) ) * xdiss(ji,jj,jk)    &
164                   &      + ( 114.   * 0.3 * trb(ji,jj,jk,jpdoc) )
[7646]165               zaggdfea = zlam1a * xstep * zfecoll
[3446]166               !
[10362]167               zlam1b   = 3.53E3 * trb(ji,jj,jk,jpgoc) * xdiss(ji,jj,jk)
[7646]168               zaggdfeb = zlam1b * xstep * zfecoll
[3446]169               !
[7646]170               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zscave - zaggdfea - zaggdfeb &
171               &                     - zcoag - precip(ji,jj,jk)
[3446]172               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zscave * zdenom1 + zaggdfea
173               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zscave * zdenom2 + zaggdfeb
[10362]174               zscav3d(ji,jj,jk)   = zscave
175               zcoll3d(ji,jj,jk)   = zaggdfea + zaggdfeb
[7646]176               !
[3443]177            END DO
178         END DO
179      END DO
180      !
[3446]181      !  Define the bioavailable fraction of iron
182      !  ----------------------------------------
[10401]183      biron(:,:,:) = trb(:,:,:,jpfer) 
[7646]184      !
185      IF( ln_ligand ) THEN
186         !
187         DO jk = 1, jpkm1
188            DO jj = 1, jpj
189               DO ji = 1, jpi
190                  zlam1a   = ( 0.369  * 0.3 * trb(ji,jj,jk,jpdoc) + 102.4  * trb(ji,jj,jk,jppoc) ) * xdiss(ji,jj,jk)    &
191                      &    + ( 114.   * 0.3 * trb(ji,jj,jk,jpdoc) )
192                  !
193                  zlam1b   = 3.53E3 *   trb(ji,jj,jk,jpgoc) * xdiss(ji,jj,jk)
[10362]194                  zligco   = 0.5 * trn(ji,jj,jk,jplgw)
[7646]195                  zaggliga = zlam1a * xstep * zligco
196                  zaggligb = zlam1b * xstep * zligco
197                  tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) - zaggliga - zaggligb
[10362]198                  zlcoll3d(ji,jj,jk)  = zaggliga + zaggligb
[7646]199               END DO
200            END DO
201         END DO
202         !
[10401]203         plig(:,:,:) =  MAX( 0., ( ( zFeL1(:,:,:) * 1E-9 ) / ( trb(:,:,:,jpfer) +rtrn ) ) )
[7646]204         !
205      ENDIF
[3443]206      !  Output of some diagnostics variables
207      !     ---------------------------------
[7646]208      IF( lk_iomput ) THEN
209         IF( knt == nrdttrc ) THEN
[10401]210            zrfact2 = 1.e3 * rfact2r  ! conversion from mol/L/timestep into mol/m3/s
211            IF( iom_use("Fe3")    )  CALL iom_put("Fe3"    , zFe3   (:,:,:)       * tmask(:,:,:) )   ! Fe3+
212            IF( iom_use("FeL1")   )  CALL iom_put("FeL1"   , zFeL1  (:,:,:)       * tmask(:,:,:) )   ! FeL1
213            IF( iom_use("TL1")    )  CALL iom_put("TL1"    , zTL1   (:,:,:)       * tmask(:,:,:) )   ! TL1
214            IF( iom_use("Totlig") )  CALL iom_put("Totlig" , ztotlig(:,:,:)       * tmask(:,:,:) )   ! TL
215            IF( iom_use("Biron")  )  CALL iom_put("Biron"  , biron  (:,:,:)  * 1e9 * tmask(:,:,:) )   ! biron
216            IF( iom_use("FESCAV") )  CALL iom_put("FESCAV" , zscav3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 )
217            IF( iom_use("FECOLL") )  CALL iom_put("FECOLL" , zcoll3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 )
218            IF( iom_use("LGWCOLL"))  CALL iom_put("LGWCOLL", zlcoll3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 )
[3443]219         ENDIF
220      ENDIF
221
222      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
[3449]223         WRITE(charout, FMT="('fechem')")
[3443]224         CALL prt_ctl_trc_info(charout)
225         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
226      ENDIF
227      !
[9124]228      IF( ln_timing )   CALL timing_stop('p4z_fechem')
[3443]229      !
230   END SUBROUTINE p4z_fechem
231
232
233   SUBROUTINE p4z_fechem_init
234      !!----------------------------------------------------------------------
235      !!                  ***  ROUTINE p4z_fechem_init  ***
236      !!
237      !! ** Purpose :   Initialization of iron chemistry parameters
238      !!
239      !! ** Method  :   Read the nampisfer namelist and check the parameters
240      !!      called at the first timestep
241      !!
242      !! ** input   :   Namelist nampisfer
243      !!
244      !!----------------------------------------------------------------------
[9124]245      INTEGER ::   ios   ! Local integer
246      !!
[10401]247      NAMELIST/nampisfer/ ln_ligvar, xlam1, xlamdust, ligand, kfep 
[9124]248      !!----------------------------------------------------------------------
[9169]249      !
250      IF(lwp) THEN
251         WRITE(numout,*)
252         WRITE(numout,*) 'p4z_rem_init : Initialization of iron chemistry parameters'
253         WRITE(numout,*) '~~~~~~~~~~~~'
254      ENDIF
255      !
[4147]256      READ  ( numnatp_ref, nampisfer, IOSTAT = ios, ERR = 901)
[11536]257901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisfer in reference namelist' )
[4147]258      READ  ( numnatp_cfg, nampisfer, IOSTAT = ios, ERR = 902 )
[11536]259902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisfer in configuration namelist' )
[9169]260      IF(lwm) WRITE( numonp, nampisfer )
[4147]261
[9169]262      IF(lwp) THEN                     ! control print
263         WRITE(numout,*) '   Namelist : nampisfer'
264         WRITE(numout,*) '      variable concentration of ligand          ln_ligvar    =', ln_ligvar
265         WRITE(numout,*) '      scavenging rate of Iron                   xlam1        =', xlam1
266         WRITE(numout,*) '      scavenging rate of Iron by dust           xlamdust     =', xlamdust
267         WRITE(numout,*) '      ligand concentration in the ocean         ligand       =', ligand
268         WRITE(numout,*) '      rate constant for nanoparticle formation  kfep         =', kfep
[3443]269      ENDIF
[10362]270      !
[3443]271   END SUBROUTINE p4z_fechem_init
[9124]272   
[3443]273   !!======================================================================
274END MODULE p4zfechem
Note: See TracBrowser for help on using the repository browser.