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_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zfechem.F90 @ 13662

Last change on this file since 13662 was 13662, checked in by clem, 4 years ago

update to almost r4.0.4

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