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 @ 13286

Last change on this file since 13286 was 13286, checked in by smasson, 4 years ago

trunk: merge extra halos branch in trunk, see #2366

  • Property svn:keywords set to Id
File size: 6.3 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          ! 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
28   !! * Substitutions
29#  include "do_loop_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
32   !! $Id$
33   !! Software governed by the CeCILL license (see ./LICENSE)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE p4z_ligand( kt, knt, Kbb, Krhs )
38      !!---------------------------------------------------------------------
39      !!                     ***  ROUTINE p4z_ligand  ***
40      !!
41      !! ** Purpose :   Compute remineralization/scavenging of organic ligands
42      !!---------------------------------------------------------------------
43      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step
44      INTEGER, INTENT(in)  ::  Kbb, Krhs ! time level indices
45      !
46      INTEGER  ::   ji, jj, jk
47      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw
48      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zligprod
49      CHARACTER (len=25) ::   charout
50      !!---------------------------------------------------------------------
51      !
52      IF( ln_timing )   CALL timing_start('p4z_ligand')
53      !
54      DO_3D_11_11( 1, jpkm1 )
55         !
56         ! ------------------------------------------------------------------
57         ! Remineralization of iron ligands
58         ! ------------------------------------------------------------------
59         ! production from remineralisation of organic matter
60         zlgwp = orem(ji,jj,jk) * rlig
61         ! decay of weak ligand
62         ! This is based on the idea that as LGW is lower
63         ! there is a larger fraction of refractory OM
64         zlgwr = max( rlgs , rlgw * exp( -2 * (tr(ji,jj,jk,jplgw,Kbb)*1e9) ) ) ! years
65         zlgwr = 1. / zlgwr * tgfunc(ji,jj,jk) * ( xstep / nyear_len(1) ) * blim(ji,jj,jk) * tr(ji,jj,jk,jplgw,Kbb)
66         ! photochem loss of weak ligand
67         zlgwpr = prlgw * xstep * etot(ji,jj,jk) * tr(ji,jj,jk,jplgw,Kbb) * (1. - fr_i(ji,jj))
68         tr(ji,jj,jk,jplgw,Krhs) = tr(ji,jj,jk,jplgw,Krhs) + zlgwp - zlgwr - zlgwpr
69         zligrem(ji,jj,jk)   = zlgwr
70         zligpr(ji,jj,jk)    = zlgwpr
71         zligprod(ji,jj,jk) = zlgwp
72         !
73      END_3D
74      !
75      !  Output of some diagnostics variables
76      !     ---------------------------------
77      IF( lk_iomput .AND. knt == nrdttrc ) THEN
78         IF( iom_use( "LIGREM" ) ) THEN
79           zligrem(:,:,jpk) = 0.  ; CALL iom_put( "LIGREM", zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
80         ENDIF
81         IF( iom_use( "LIGPR" ) ) THEN
82           zligpr(:,:,jpk) = 0.   ; CALL iom_put( "LIGPR" , zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
83         ENDIF
84         IF( iom_use( "LPRODR" ) ) THEN
85           zligprod(:,:,jpk) = 0. ; CALL iom_put( "LPRODR", zligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
86         ENDIF
87      ENDIF
88      !
89      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
90         WRITE(charout, FMT="('ligand1')")
91         CALL prt_ctl_info( charout, cdcomp = 'top' )
92         CALL prt_ctl(tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm)
93      ENDIF
94      !
95      IF( ln_timing )   CALL timing_stop('p4z_ligand')
96      !
97   END SUBROUTINE p4z_ligand
98
99
100   SUBROUTINE p4z_ligand_init
101      !!----------------------------------------------------------------------
102      !!                  ***  ROUTINE p4z_ligand_init  ***
103      !!
104      !! ** Purpose :   Initialization of remineralization parameters
105      !!
106      !! ** Method  :   Read the nampislig namelist and check the parameters
107      !!
108      !! ** input   :   Namelist nampislig
109      !!----------------------------------------------------------------------
110      INTEGER ::   ios   ! Local integer
111      !
112      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rlig
113      !!----------------------------------------------------------------------
114      !
115      IF(lwp) THEN
116         WRITE(numout,*)
117         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands'
118         WRITE(numout,*) '~~~~~~~~~~~~~~~'
119      ENDIF
120      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901)
121901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist' )
122      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 )
123902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampislig in configuration namelist' )
124      IF(lwm) WRITE ( numonp, nampislig )
125      !
126      IF(lwp) THEN                         ! control print
127         WRITE(numout,*) '   Namelist : nampislig'
128         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw
129         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig
130         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw
131         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs
132      ENDIF
133      !
134   END SUBROUTINE p4z_ligand_init
135
136   !!======================================================================
137END MODULE p4zligand
Note: See TracBrowser for help on using the repository browser.