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.
p4zligand.F90 in NEMO/trunk/src/TOP/PISCES/P4Z – NEMO

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

Last change on this file was 15459, checked in by cetlod, 2 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: 7.4 KB
RevLine 
[7162]1MODULE p4zligand
2   !!======================================================================
3   !!                         ***  MODULE p4zligand  ***
4   !! TOP :   PISCES Compute remineralization/dissolution of organic ligands
5   !!=========================================================================
6   !! History :   3.6  !  2016-03  (O. Aumont, A. Tagliabue) Quota model and reorganization
7   !!----------------------------------------------------------------------
[9169]8   !!   p4z_ligand     :  Compute remineralization/dissolution of organic ligands
9   !!   p4z_ligand_init:  Initialisation of parameters for remineralisation
[7162]10   !!----------------------------------------------------------------------
[9169]11   USE oce_trc         ! shared variables between ocean and passive tracers
12   USE trc             ! passive tracers common variables
13   USE sms_pisces      ! PISCES Source Minus Sink variables
[13286]14   USE prtctl          ! print control for debugging
[10362]15   USE iom             !  I/O manager
[7162]16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   p4z_ligand         ! called in p4zbio.F90
21   PUBLIC   p4z_ligand_init    ! called in trcsms_pisces.F90
22
23   REAL(wp), PUBLIC ::  rlgw     !: lifetime (years) of weak ligands
24   REAL(wp), PUBLIC ::  rlgs     !: lifetime (years) of strong ligands
25   REAL(wp), PUBLIC ::  rlig     !: Remin ligand production
26   REAL(wp), PUBLIC ::  prlgw    !: Photochemical of weak ligand
[15459]27   REAL(wp), PUBLIC ::  xklig    !: 1/2 saturation constant of photolysis
[7162]28
[12377]29   !! * Substitutions
30#  include "do_loop_substitute.h90"
[7162]31   !!----------------------------------------------------------------------
[10067]32   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[10069]33   !! $Id$
[10068]34   !! Software governed by the CeCILL license (see ./LICENSE)
[7162]35   !!----------------------------------------------------------------------
36CONTAINS
37
[12377]38   SUBROUTINE p4z_ligand( kt, knt, Kbb, Krhs )
[7162]39      !!---------------------------------------------------------------------
40      !!                     ***  ROUTINE p4z_ligand  ***
41      !!
42      !! ** Purpose :   Compute remineralization/scavenging of organic ligands
43      !!---------------------------------------------------------------------
[12377]44      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step
45      INTEGER, INTENT(in)  ::  Kbb, Krhs ! time level indices
[7162]46      !
47      INTEGER  ::   ji, jj, jk
[15459]48      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw 
49      REAL(wp) ::   zlam1a, zlam1b, zaggliga, zligco
50      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zligprod, zlcoll3d
[9169]51      CHARACTER (len=25) ::   charout
[7162]52      !!---------------------------------------------------------------------
53      !
[9124]54      IF( ln_timing )   CALL timing_start('p4z_ligand')
[7162]55      !
[15090]56      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1)
[12377]57         !
58         ! ------------------------------------------------------------------
59         ! Remineralization of iron ligands
60         ! ------------------------------------------------------------------
61         ! production from remineralisation of organic matter
62         zlgwp = orem(ji,jj,jk) * rlig
63         ! decay of weak ligand
64         ! This is based on the idea that as LGW is lower
65         ! there is a larger fraction of refractory OM
[15459]66         zlgwr = ( 1.0 / rlgs * MAX(0., tr(ji,jj,jk,jplgw,Kbb) - xfecolagg(ji,jj,jk) * 1.0E-9 )    &
67         &       + 1.0 / rlgw * xfecolagg(ji,jj,jk) * 1.0E-9 ) / ( rtrn + tr(ji,jj,jk,jplgw,Kbb) )
68         zlgwr = zlgwr * tgfunc(ji,jj,jk) * ( xstep / nyear_len(1) ) * blim(ji,jj,jk) * tr(ji,jj,jk,jplgw,Kbb)
[12377]69         ! photochem loss of weak ligand
[15459]70         zlgwpr = prlgw * xstep * etot(ji,jj,jk) * tr(ji,jj,jk,jplgw,Kbb)**3 * (1. - fr_i(ji,jj))   &
71         &        / ( tr(ji,jj,jk,jplgw,Kbb)**2 + (xklig)**2)
72         ! Coagulation of ligands due to various processes (Brownian, shear, diff. sedimentation
73         ! xcoagfe is computed in p4zfechem
74         ! -------------------------------------------------------------------------------------
75         ! 50% of the ligands are supposed to be in the colloidal size fraction
76         ! as for FeL
77         zligco   = 0.5 * MAX(0., tr(ji,jj,jk,jplgw,Kbb) - xfecolagg(ji,jj,jk) * 1.0E-9 )
78         zaggliga = xcoagfe(ji,jj,jk) * xstep * zligco
79
80         tr(ji,jj,jk,jplgw,Krhs) = tr(ji,jj,jk,jplgw,Krhs) + zlgwp - zlgwr - zlgwpr - zaggliga
81         !
[12377]82         zligrem(ji,jj,jk)   = zlgwr
83         zligpr(ji,jj,jk)    = zlgwpr
[15459]84         zligprod(ji,jj,jk)  = zlgwp
85         zlcoll3d(ji,jj,jk)  = zaggliga
[12377]86      END_3D
[9169]87      !
[10362]88      !  Output of some diagnostics variables
89      !     ---------------------------------
90      IF( lk_iomput .AND. knt == nrdttrc ) THEN
91         IF( iom_use( "LIGREM" ) ) THEN
[12276]92           zligrem(:,:,jpk) = 0.  ; CALL iom_put( "LIGREM", zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
[10362]93         ENDIF
94         IF( iom_use( "LIGPR" ) ) THEN
[12276]95           zligpr(:,:,jpk) = 0.   ; CALL iom_put( "LIGPR" , zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
[10362]96         ENDIF
97         IF( iom_use( "LPRODR" ) ) THEN
[12276]98           zligprod(:,:,jpk) = 0. ; CALL iom_put( "LPRODR", zligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
[10362]99         ENDIF
[15459]100         IF( iom_use( "LGWCOLL" ) ) THEN
101            zlcoll3d(:,:,jpk) = 0. ; CALL iom_put( "LGWCOLL", zlcoll3d(:,:,:) * 1.e9 *  1.e+3 * rfact2r * tmask(:,:,:) )
102         ENDIF
[10362]103      ENDIF
104      !
[12377]105      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
[7162]106         WRITE(charout, FMT="('ligand1')")
[13286]107         CALL prt_ctl_info( charout, cdcomp = 'top' )
108         CALL prt_ctl(tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm)
[9169]109      ENDIF
[7162]110      !
[9124]111      IF( ln_timing )   CALL timing_stop('p4z_ligand')
[7162]112      !
113   END SUBROUTINE p4z_ligand
114
115
116   SUBROUTINE p4z_ligand_init
117      !!----------------------------------------------------------------------
118      !!                  ***  ROUTINE p4z_ligand_init  ***
119      !!
120      !! ** Purpose :   Initialization of remineralization parameters
121      !!
122      !! ** Method  :   Read the nampislig namelist and check the parameters
123      !!
124      !! ** input   :   Namelist nampislig
125      !!----------------------------------------------------------------------
[9124]126      INTEGER ::   ios   ! Local integer
127      !
[15459]128      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rlig, xklig
[9124]129      !!----------------------------------------------------------------------
[9169]130      !
131      IF(lwp) THEN
132         WRITE(numout,*)
133         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands'
134         WRITE(numout,*) '~~~~~~~~~~~~~~~'
135      ENDIF
[7162]136      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901)
[11536]137901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist' )
[7162]138      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 )
[11536]139902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampislig in configuration namelist' )
[7162]140      IF(lwm) WRITE ( numonp, nampislig )
[9169]141      !
[7162]142      IF(lwp) THEN                         ! control print
[9169]143         WRITE(numout,*) '   Namelist : nampislig'
144         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw
145         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig
146         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw
147         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs
[15459]148         WRITE(numout,*) '      1/2 saturation for photolysis                xklig =', xklig
[7162]149      ENDIF
150      !
151   END SUBROUTINE p4z_ligand_init
152
153   !!======================================================================
154END MODULE p4zligand
Note: See TracBrowser for help on using the repository browser.