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

Last change on this file since 10345 was 10069, checked in by nicolasmartin, 6 years ago

Fix mistakes of previous commit on SVN keywords property

  • Property svn:keywords set to Id
File size: 6.5 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
14   USE prtctl_trc      ! print control for debugging
[7162]15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC   p4z_ligand         ! called in p4zbio.F90
20   PUBLIC   p4z_ligand_init    ! called in trcsms_pisces.F90
21
22   REAL(wp), PUBLIC ::  rlgw     !: lifetime (years) of weak ligands
23   REAL(wp), PUBLIC ::  rlgs     !: lifetime (years) of strong ligands
24   REAL(wp), PUBLIC ::  rlig     !: Remin ligand production
25   REAL(wp), PUBLIC ::  prlgw    !: Photochemical of weak ligand
26   REAL(wp), PUBLIC ::  rfep     !: Dissolution rate of FeP
27
28   !!----------------------------------------------------------------------
[10067]29   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[10069]30   !! $Id$
[10068]31   !! Software governed by the CeCILL license (see ./LICENSE)
[7162]32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE p4z_ligand( kt, knt )
36      !!---------------------------------------------------------------------
37      !!                     ***  ROUTINE p4z_ligand  ***
38      !!
39      !! ** Purpose :   Compute remineralization/scavenging of organic ligands
40      !!---------------------------------------------------------------------
41      INTEGER, INTENT(in) ::   kt, knt ! ocean time step
42      !
43      INTEGER  ::   ji, jj, jk
44      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr
[9169]45      CHARACTER (len=25) ::   charout
[7162]46      !!---------------------------------------------------------------------
47      !
[9124]48      IF( ln_timing )   CALL timing_start('p4z_ligand')
[7162]49      !
50      DO jk = 1, jpkm1
51         DO jj = 1, jpj
52            DO ji = 1, jpi
[9169]53               !
54               ! ------------------------------------------------------------------
55               ! Remineralization of iron ligands
56               ! ------------------------------------------------------------------
[7162]57               ! production from remineralisation of organic matter
58               zlgwp  = orem(ji,jj,jk) * rlig
59               ! decay of weak ligand
60               ! This is based on the idea that as LGW is lower
61               ! there is a larger fraction of refractory OM
[7177]62               zlgwr = max( rlgs , rlgw * exp( -2 * (trb(ji,jj,jk,jplgw)*1e9) ) ) ! years
63               zlgwr = 1. / zlgwr * tgfunc(ji,jj,jk) * ( xstep / nyear_len(1) ) * trb(ji,jj,jk,jplgw)
[7162]64               ! photochem loss of weak ligand
[7177]65               zlgwpr = prlgw * xstep * etot(ji,jj,jk) * trb(ji,jj,jk,jplgw) * (1. - fr_i(ji,jj))
[7162]66               tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zlgwp - zlgwr - zlgwpr
[9169]67               !
68               ! ----------------------------------------------------------
69               ! Dissolution of nanoparticle Fe
70               ! ----------------------------------------------------------
[7162]71               ! dissolution rate is maximal in the presence of light and
72               ! lower in the aphotici zone
73               ! ! 25 Wm-2 constant
74               zrfepa = rfep * ( 1. - EXP( -1. * etot(ji,jj,jk) / 25. ) ) * (1.- fr_i(ji,jj))
75               zrfepa = MAX( (zrfepa / 10.0), zrfepa ) ! min of 10 days lifetime
[7177]76               zfepr = rfep * xstep * trb(ji,jj,jk,jpfep)
[7162]77               tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr
78               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr
[9169]79               !
[7162]80            END DO
81         END DO
82      END DO
[9169]83      !
[7162]84      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
85         WRITE(charout, FMT="('ligand1')")
86         CALL prt_ctl_trc_info(charout)
87         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
[9169]88      ENDIF
[7162]89      !
[9124]90      IF( ln_timing )   CALL timing_stop('p4z_ligand')
[7162]91      !
92   END SUBROUTINE p4z_ligand
93
94
95   SUBROUTINE p4z_ligand_init
96      !!----------------------------------------------------------------------
97      !!                  ***  ROUTINE p4z_ligand_init  ***
98      !!
99      !! ** Purpose :   Initialization of remineralization parameters
100      !!
101      !! ** Method  :   Read the nampislig namelist and check the parameters
102      !!
103      !! ** input   :   Namelist nampislig
104      !!----------------------------------------------------------------------
[9124]105      INTEGER ::   ios   ! Local integer
106      !
[7162]107      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig
[9124]108      !!----------------------------------------------------------------------
[9169]109      !
110      IF(lwp) THEN
111         WRITE(numout,*)
112         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands'
113         WRITE(numout,*) '~~~~~~~~~~~~~~~'
114      ENDIF
[7162]115      REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization
116      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901)
[9169]117901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp )
[7162]118      REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization
119      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 )
[9169]120902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp )
[7162]121      IF(lwm) WRITE ( numonp, nampislig )
[9169]122      !
[7162]123      IF(lwp) THEN                         ! control print
[9169]124         WRITE(numout,*) '   Namelist : nampislig'
125         WRITE(numout,*) '      Dissolution rate of FeP                      rfep  =', rfep
126         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw
127         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig
128         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw
129         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs
[7162]130      ENDIF
131      !
132   END SUBROUTINE p4z_ligand_init
133
134   !!======================================================================
135END MODULE p4zligand
Note: See TracBrowser for help on using the repository browser.