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 branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zligand.F90 @ 8003

Last change on this file since 8003 was 8003, checked in by aumont, 7 years ago

modification in the code to remove unnecessary parts such as kriest and non iomput options

File size: 9.0 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#if defined key_pisces || defined key_pisces_quota
9# if defined key_ligand
10   !!----------------------------------------------------------------------
11   !!   'key_top'       and                                      TOP models
12   !!   'key_pisces*'   and                                PISCES bio-model
13   !!   'key_ligand'                                        Ligand submodel
14   !!----------------------------------------------------------------------
15   !!   p4z_ligand       :  Compute remineralization/dissolution of organic ligands
16   !!   p4z_ligand_init  :  Initialisation of parameters for remineralisation
17   !!----------------------------------------------------------------------
18   USE oce_trc         !  shared variables between ocean and passive tracers
19   USE trc             !  passive tracers common variables
20   USE sms_pisces      !  PISCES Source Minus Sink variables
21   USE p4zopt          !  optical model
22   USE prtctl_trc      !  print control for debugging
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   p4z_ligand         ! called in p4zbio.F90
28   PUBLIC   p4z_ligand_init    ! called in trcsms_pisces.F90
29
30   !! * Shared module variables
31   REAL(wp), PUBLIC ::  rlgw     !: lifetime (years) of weak ligands
32   REAL(wp), PUBLIC ::  rlgs     !: lifetime (years) of strong ligands
33   REAL(wp), PUBLIC ::  rlig     !: Remin ligand production
34   REAL(wp), PUBLIC ::  prlgw    !: Photochemical of weak ligand
35   REAL(wp), PUBLIC ::  rfep     !: Dissolution rate of FeP
36
37
38   !!* Substitution
39#  include "top_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
42   !! $Id: p4zligand.F90 3160 2011-11-20 14:27:18Z cetlod $
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE p4z_ligand( kt, jnt )
48      !!---------------------------------------------------------------------
49      !!                     ***  ROUTINE p4z_ligand  ***
50      !!
51      !! ** Purpose :   Compute remineralization/scavenging of organic ligands
52      !!
53      !! ** Method  : - ???
54      !!---------------------------------------------------------------------
55      !
56      INTEGER, INTENT(in) ::   kt, jnt ! ocean time step
57      !
58      INTEGER  ::   ji, jj, jk
59      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr
60      REAL(wp) ::   zstep, zstep2, zrfact2
61      REAL(wp), POINTER, DIMENSION(:,:,:) :: zligrem, zligpr, zrligprod
62      CHARACTER (len=25) :: charout
63      !!---------------------------------------------------------------------
64      !
65      IF( nn_timing == 1 )  CALL timing_start('p4z_ligand')
66      !
67      CALL wrk_alloc( jpi, jpj, jpk, zligrem, zligpr, zrligprod )
68      !
69      ! ------------------------------------------------------------------
70      ! Remineralization of iron ligands
71      ! ------------------------------------------------------------------
72      DO jk = 1, jpkm1
73         DO jj = 1, jpj
74            DO ji = 1, jpi
75               ! ----------------------------------------------------------
76               ! zstep converts per day to per timestep
77               ! zstep for the yearly rates
78               ! ---------------------------------------------------------
79               zstep   = xstep
80               zstep2  = zstep / 365. ! per year
81               ! production from remineralisation of organic matter
82               zlgwp  = orem(ji,jj,jk) * rlig
83               ! decay of weak ligand
84               ! This is based on the idea that as LGW is lower
85               ! there is a larger fraction of refractory OM
86               zlgwr = max( rlgs , rlgw * exp( -2 * (trn(ji,jj,jk,jplgw)*1e9) ) ) ! years
87               zlgwr = 1. / zlgwr * tgfunc(ji,jj,jk) * zstep2 * trn(ji,jj,jk,jplgw)
88               ! photochem loss of weak ligand
89               zlgwpr = prlgw * zstep * etot(ji,jj,jk) * trn(ji,jj,jk,jplgw) * (1. - fr_i(ji,jj))
90               tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zlgwp - zlgwr - zlgwpr
91               zligrem(ji,jj,jk)   = zlgwr
92               zligpr(ji,jj,jk)    = zlgwpr
93               zrligprod(ji,jj,jk) = zlgwp
94            END DO
95         END DO
96      END DO
97
98      ! ----------------------------------------------------------
99      ! Dissolution of nanoparticle Fe
100      ! ----------------------------------------------------------
101
102      DO jk = 1, jpkm1
103         DO jj = 1, jpj
104            DO ji = 1, jpi
105               ! dissolution rate is maximal in the presence of light and
106               ! lower in the aphotici zone
107               ! ! 25 Wm-2 constant
108               zrfepa = rfep * (1- EXP(-etot(ji,jj,jk) / 25. ) ) * (1.- fr_i(ji,jj))
109               zrfepa = MAX( (zrfepa / 10.0), zrfepa ) ! min of 10 days lifetime
110               zfepr = rfep * zstep * trn(ji,jj,jk,jpfep)
111               tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr
112               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr
113            END DO
114         END DO
115      END DO
116
117      !  Output of some diagnostics variables
118      !     ---------------------------------
119      IF( ln_diatrc .AND. lk_iomput ) THEN
120         IF( jnt == nrdttrc ) THEN
121            CALL iom_put("LIGREM"   , zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
122            CALL iom_put("LIGPR"    , zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
123            CALL iom_put("LPRODR"   , zrligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
124         ENDIF
125      ENDIF
126
127      CALL wrk_dealloc( jpi, jpj, jpk, zligrem, zligpr, zrligprod )
128
129      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
130         WRITE(charout, FMT="('ligand1')")
131         CALL prt_ctl_trc_info(charout)
132         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
133       ENDIF
134      !
135      IF( nn_timing == 1 )  CALL timing_stop('p4z_ligand')
136      !
137   END SUBROUTINE p4z_ligand
138
139
140   SUBROUTINE p4z_ligand_init
141      !!----------------------------------------------------------------------
142      !!                  ***  ROUTINE p4z_ligand_init  ***
143      !!
144      !! ** Purpose :   Initialization of remineralization parameters
145      !!
146      !! ** Method  :   Read the nampislig namelist and check the parameters
147      !!      called at the first timestep
148      !!
149      !! ** input   :   Namelist nampislig
150      !!
151      !!----------------------------------------------------------------------
152      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig
153      INTEGER :: ios                 ! Local integer output status for namelist read
154
155      REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization
156      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901)
157901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp )
158
159      REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization
160      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 )
161902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp )
162      IF(lwm) WRITE ( numonp, nampislig )
163
164      IF(lwp) THEN                         ! control print
165         WRITE(numout,*) ' '
166         WRITE(numout,*) ' Namelist parameters for ligands, nampislig'
167         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
168         WRITE(numout,*) '    Dissolution rate of FeP                        rfep =', rfep
169         WRITE(numout,*) '    Lifetime (years) of weak ligands               rlgw =', rlgw
170         WRITE(numout,*) '    Remin ligand production per unit C             rlig =', rlig
171         WRITE(numout,*) '    Photolysis of weak ligand                     prlgw =', prlgw
172         WRITE(numout,*) '    Lifetime (years) of strong ligands             rlgs =', rlgs
173      ENDIF
174      !
175   END SUBROUTINE p4z_ligand_init
176
177# else
178   !!======================================================================
179   !!  Dummy module :                                  No ligands sub-model
180   !!======================================================================
181CONTAINS
182   SUBROUTINE p4z_ligand(kt, jnt)                    ! Empty routine
183      INTEGER, INTENT(in) ::   kt, jnt ! ocean time step
184   END SUBROUTINE p4z_ligand
185# endif
186#else
187   !!======================================================================
188   !!  Dummy module :                                   No PISCES bio-model
189   !!======================================================================
190CONTAINS
191   SUBROUTINE p4z_ligand                    ! Empty routine
192   END SUBROUTINE p4z_ligand
193#endif 
194
195   !!======================================================================
196END MODULE p4zligand
Note: See TracBrowser for help on using the repository browser.