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_r8832_PISCO/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/CNRS/dev_r8832_PISCO/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zligand.F90 @ 9450

Last change on this file since 9450 was 9450, checked in by aumont, 6 years ago

debug PISCES code

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