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/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/P4Z/p4zligand.F90 @ 10377

Last change on this file since 10377 was 10368, checked in by smasson, 5 years ago

dev_r10164_HPC09_ESIWACE_PREP_MERGE: merge with trunk@10365, see #2133

  • Property svn:keywords set to Id
File size: 7.6 KB
Line 
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   !!----------------------------------------------------------------------
8   !!   p4z_ligand     :  Compute remineralization/dissolution of organic ligands
9   !!   p4z_ligand_init:  Initialisation of parameters for remineralisation
10   !!----------------------------------------------------------------------
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
14   USE prtctl_trc      ! print control for debugging
15   USE iom             !  I/O manager
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
27   REAL(wp), PUBLIC ::  rfep     !: Dissolution rate of FeP
28
29   !!----------------------------------------------------------------------
30   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
31   !! $Id$
32   !! Software governed by the CeCILL license (see ./LICENSE)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE p4z_ligand( kt, knt )
37      !!---------------------------------------------------------------------
38      !!                     ***  ROUTINE p4z_ligand  ***
39      !!
40      !! ** Purpose :   Compute remineralization/scavenging of organic ligands
41      !!---------------------------------------------------------------------
42      INTEGER, INTENT(in) ::   kt, knt ! ocean time step
43      !
44      INTEGER  ::   ji, jj, jk
45      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr
46      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zrligprod
47      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d
48      CHARACTER (len=25) ::   charout
49      !!---------------------------------------------------------------------
50      !
51      IF( ln_timing )   CALL timing_start('p4z_ligand')
52      !
53      DO jk = 1, jpkm1
54         DO jj = 1, jpj
55            DO ji = 1, jpi
56               !
57               ! ------------------------------------------------------------------
58               ! Remineralization of iron ligands
59               ! ------------------------------------------------------------------
60               ! production from remineralisation of organic matter
61               zlgwp = orem(ji,jj,jk) * rlig
62               ! decay of weak ligand
63               ! This is based on the idea that as LGW is lower
64               ! there is a larger fraction of refractory OM
65               zlgwr = max( rlgs , rlgw * exp( -2 * (trb(ji,jj,jk,jplgw)*1e9) ) ) ! years
66               zlgwr = 1. / zlgwr * tgfunc(ji,jj,jk) * ( xstep / nyear_len(1) ) * blim(ji,jj,jk) * trb(ji,jj,jk,jplgw)
67               ! photochem loss of weak ligand
68               zlgwpr = prlgw * xstep * etot(ji,jj,jk) * trb(ji,jj,jk,jplgw) * (1. - fr_i(ji,jj))
69               tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zlgwp - zlgwr - zlgwpr
70               zligrem(ji,jj,jk)   = zlgwr
71               zligpr(ji,jj,jk)    = zlgwpr
72               zrligprod(ji,jj,jk) = zlgwp
73               !
74               ! ----------------------------------------------------------
75               ! Dissolution of nanoparticle Fe
76               ! ----------------------------------------------------------
77               ! dissolution rate is maximal in the presence of light and
78               ! lower in the aphotici zone
79               ! ! 25 Wm-2 constant
80               zrfepa = rfep * ( 1. - EXP( -1. * etot(ji,jj,jk) / 25. ) ) * (1.- fr_i(ji,jj))
81               zrfepa = MAX( (zrfepa / 10.0), zrfepa ) ! min of 10 days lifetime
82               zfepr  = rfep * xstep * trb(ji,jj,jk,jpfep)
83               tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr
84               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr
85               !
86            END DO
87         END DO
88      END DO
89      !
90      !  Output of some diagnostics variables
91      !     ---------------------------------
92      IF( lk_iomput .AND. knt == nrdttrc ) THEN
93         ALLOCATE( zw3d(jpi,jpj,jpk) )
94         IF( iom_use( "LIGREM" ) ) THEN
95            zw3d(:,:,:) = zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)
96            CALL iom_put( "LIGREM", zw3d )
97         ENDIF
98         IF( iom_use( "LIGPR" ) ) THEN
99            zw3d(:,:,:) = zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
100            CALL iom_put( "LIGPR", zw3d )
101         ENDIF
102         IF( iom_use( "LPRODR" ) ) THEN
103            zw3d(:,:,:) = zrligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
104            CALL iom_put( "LPRODR", zw3d )
105         ENDIF
106         DEALLOCATE( zw3d )
107      ENDIF
108      !
109      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
110         WRITE(charout, FMT="('ligand1')")
111         CALL prt_ctl_trc_info(charout)
112         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
113      ENDIF
114      !
115      IF( ln_timing )   CALL timing_stop('p4z_ligand')
116      !
117   END SUBROUTINE p4z_ligand
118
119
120   SUBROUTINE p4z_ligand_init
121      !!----------------------------------------------------------------------
122      !!                  ***  ROUTINE p4z_ligand_init  ***
123      !!
124      !! ** Purpose :   Initialization of remineralization parameters
125      !!
126      !! ** Method  :   Read the nampislig namelist and check the parameters
127      !!
128      !! ** input   :   Namelist nampislig
129      !!----------------------------------------------------------------------
130      INTEGER ::   ios   ! Local integer
131      !
132      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig
133      !!----------------------------------------------------------------------
134      !
135      IF(lwp) THEN
136         WRITE(numout,*)
137         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands'
138         WRITE(numout,*) '~~~~~~~~~~~~~~~'
139      ENDIF
140      REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization
141      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901)
142901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp )
143      REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization
144      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 )
145902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp )
146      IF(lwm) WRITE ( numonp, nampislig )
147      !
148      IF(lwp) THEN                         ! control print
149         WRITE(numout,*) '   Namelist : nampislig'
150         WRITE(numout,*) '      Dissolution rate of FeP                      rfep  =', rfep
151         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw
152         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig
153         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw
154         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs
155      ENDIF
156      !
157   END SUBROUTINE p4z_ligand_init
158
159   !!======================================================================
160END MODULE p4zligand
Note: See TracBrowser for help on using the repository browser.