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.
p4zrem.F in branches/dev_001_GM/NEMO/TOP_SRC/PISCES_SMS – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/PISCES_SMS/p4zrem.F @ 772

Last change on this file since 772 was 772, checked in by gm, 16 years ago

dev_001_GM - change the name of cpp key to key_top, key_lobster, key_pisces, key_kriest and the corresponding lk_

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 8.4 KB
RevLine 
[341]1
[725]2CCC $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/SMS/p4zrem.F,v 1.8 2007/10/12 09:28:41 opalod Exp $ 
[341]3CCC  TOP 1.0 , LOCEAN-IPSL (2005) 
4C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
5C ---------------------------------------------------------------------------
[186]6CDIR$ LIST
7      SUBROUTINE p4zrem
[772]8#if defined key_top && defined key_pisces
[186]9CCC---------------------------------------------------------------------
10CCC
11CCC          ROUTINE p4zrem : PISCES MODEL
12CCC          *****************************
13CCC
14CCC  PURPOSE :
15CCC  ---------
16CCC         Compute remineralization/scavenging of organic compounds
17CCC
18CC   INPUT :
19CC   -----
20CC      common
21CC              all the common defined in opa
22CC
23CC
24CC   OUTPUT :                   : no
25CC   ------
26CC
27CC   EXTERNAL :
28CC   --------
29CC            None
30CC
31CC   MODIFICATIONS:
32CC   --------------
33CC      original  : 2004 - O. Aumont 
34CC----------------------------------------------------------------------
35CC parameters and commons
36CC ======================
37CDIR$ NOLIST
38      USE oce_trc
39      USE trp_trc
40      USE sms
41      IMPLICIT NONE
[339]42#include "domzgr_substitute.h90"
[186]43CDIR$ LIST
44CC----------------------------------------------------------------------
45CC local declarations
46CC ==================
47      INTEGER ji, jj, jk
48      REAL remip,remik,xlam1b
49      REAL xkeq,xfeequi,siremin
[339]50      REAL zsatur,zsatur2,znusil,zdepbac(jpi,jpj,jpk)
51      REAL zlamfac,zstep,fesatur(jpi,jpj,jpk)
[725]52      REAL ztempbac(jpi,jpj)
[186]53C
[339]54C      Time step duration for the biology
55C
56       zstep=rfact2/rjjss
57C
[186]58C      Computation of the mean phytoplankton concentration as
59C      a crude estimate of the bacterial biomass
60C      --------------------------------------------------
61C
[725]62        DO jk=1,jpkm1
63          DO jj = 1, jpj
64            DO ji = 1, jpi
65         IF (fsdept(ji,jj,jk).lt.120.) THEN
66         zdepbac(ji,jj,jk)=min(0.7*(trn(ji,jj,jk,jpzoo)
67     &     +2*trn(ji,jj,jk,jpmes)),4E-6)
68         ztempbac(ji,jj)=zdepbac(ji,jj,jk)
69         ELSE
70         zdepbac(ji,jj,jk)=min(1.,120./fsdept(ji,jj,jk))
71     &      *ztempbac(ji,jj)
72         ENDIF
73            END DO
74          END DO
[339]75        END DO
[186]76
[339]77         DO jk = 1,jpkm1
[186]78           DO jj = 1,jpj
79             DO ji = 1,jpi
80C
81C    DENITRIFICATION FACTOR COMPUTED FROM O2 LEVELS
82C    ----------------------------------------------
83C
84          nitrfac(ji,jj,jk)=
85     &      max(0.,0.4*(6.E-6-trn(ji,jj,jk,jpoxy))/(oxymin+
86     &      trn(ji,jj,jk,jpoxy)))
87             END DO
88           END DO
89         END DO
90
[339]91          nitrfac(:,:,:)=min(1.,nitrfac(:,:,:))
92
[186]93         DO jk = 1,jpkm1
94           DO jj = 1,jpj
95             DO ji = 1,jpi
96C
97C     DOC ammonification. Depends on depth, phytoplankton biomass
98C     and a limitation term which is supposed to be a parameterization
99C     of the bacterial activity. 
100C     ----------------------------------------------------------------
[339]101C
102         remik = xremik*zstep/1E-6*xlimbac(ji,jj,jk)
103     &     *zdepbac(ji,jj,jk)
[186]104#    if defined key_off_degrad
105     &     *facvol(ji,jj,jk)
106#    endif
[339]107         remik=max(remik,5.5E-4*zstep)
[186]108C
109C     Ammonification in oxic waters with oxygen consumption
110C     -----------------------------------------------------
111C
112         olimi(ji,jj,jk)=min((trn(ji,jj,jk,jpoxy)-rtrn)/o2ut,
113     &     remik*(1.-nitrfac(ji,jj,jk))*trn(ji,jj,jk,jpdoc)) 
114C
115C     Ammonification in suboxic waters with denitrification
116C     -------------------------------------------------------
117C
[339]118         denitr(ji,jj,jk)=min((trn(ji,jj,jk,jpno3)-rtrn)/rdenit,
[186]119     &     remik*nitrfac(ji,jj,jk)*trn(ji,jj,jk,jpdoc))
120             END DO
121           END DO
122         END DO
[339]123C
124         olimi(:,:,:)=max(0.,olimi(:,:,:))
125         denitr(:,:,:)=max(0.,denitr(:,:,:))
126C
[186]127         DO jk = 1,jpkm1
128           DO jj = 1,jpj
129             DO ji = 1,jpi
130C
131C    NH4 nitrification to NO3. Ceased for oxygen concentrations
132C    below 2 umol/L. Inhibited at strong light 
133C    ----------------------------------------------------------
134C
[339]135         onitr(ji,jj,jk)=nitrif*zstep*trn(ji,jj,jk,jpnh4)/(1.
136     &     +emoy(ji,jj,jk))*(1.-nitrfac(ji,jj,jk))
[186]137#    if defined key_off_degrad
138     &     *facvol(ji,jj,jk)
139#    endif
140             END DO
141           END DO
142         END DO
143
144         DO jk = 1,jpkm1
145           DO jj = 1,jpj
146             DO ji = 1,jpi
147C
148C    Bacterial uptake of iron. No iron is available in DOC. So
149C    Bacteries are obliged to take up iron from the water. Some
150C    studies (especially at Papa) have shown this uptake to be
151C    significant
152C    ----------------------------------------------------------
153C
[339]154         xbactfer(ji,jj,jk)=15E-6*rfact2*4.*0.4*prmax(ji,jj,jk)
155     &     *(xlimphy(ji,jj,jk)*zdepbac(ji,jj,jk))**2
156     &     /(xkgraz2+zdepbac(ji,jj,jk))
157     &     *(0.5+sign(0.5,trn(ji,jj,jk,jpfer)-2E-11))
158C
[186]159             END DO
160           END DO
161         END DO
162C
163         DO jk = 1,jpkm1
164           DO jj = 1,jpj
165             DO ji = 1,jpi
166C
167C    POC disaggregation by turbulence and bacterial activity. 
168C    -------------------------------------------------------------
169C
[339]170         remip=xremip*zstep*tgfunc(ji,jj,jk)*(1.-0.5*nitrfac(ji,jj,jk))
[186]171#    if defined key_off_degrad
172     &     *facvol(ji,jj,jk)
173#    endif
174C
175C    POC disaggregation rate is reduced in anoxic zone as shown by
176C    sediment traps data. In oxic area, the exponent of the martin's
177C    law is around -0.87. In anoxic zone, it is around -0.35. This
178C    means a disaggregation constant about 0.5 the value in oxic zones
179C    -----------------------------------------------------------------
180C
181         orem(ji,jj,jk)=remip*trn(ji,jj,jk,jppoc)
[617]182         ofer(ji,jj,jk)=remip*trn(ji,jj,jk,jpsfe)
[772]183#if ! defined key_kriest
[186]184         orem2(ji,jj,jk)=remip*trn(ji,jj,jk,jpgoc)
185         ofer2(ji,jj,jk)=remip*trn(ji,jj,jk,jpbfe)
[617]186#else
187         orem2(ji,jj,jk)=remip*trn(ji,jj,jk,jpnum)
188#endif
[186]189C
190             END DO
191           END DO
192         END DO
193
194         DO jk = 1,jpkm1
195           DO jj = 1,jpj
196             DO ji = 1,jpi
197C
198C     Remineralization rate of BSi depedant on T and saturation
199C     ---------------------------------------------------------
200C
201         zsatur=(sio3eq(ji,jj,jk)-trn(ji,jj,jk,jpsil))/
202     &     (sio3eq(ji,jj,jk)+rtrn)
[339]203         zsatur=max(rtrn,zsatur)
204         zsatur2=zsatur*(1.+tn(ji,jj,jk)/400.)**4
205         znusil=0.225*(1.+tn(ji,jj,jk)/15.)*zsatur+0.775*zsatur2**9
[260]206
[339]207         siremin=xsirem*zstep*znusil
[186]208#    if defined key_off_degrad
209     &     *facvol(ji,jj,jk)
210#    endif
211C
212         osil(ji,jj,jk)=siremin*trn(ji,jj,jk,jpdsi)
213             END DO
214           END DO
215         END DO
[339]216C
217         fesatur(:,:,:)=0.6E-9
218C
[186]219         DO jk = 1,jpkm1
220           DO jj = 1,jpj
221             DO ji = 1,jpi
222C
223C     scavenging rate of iron. this scavenging rate depends on the
224C     load in particles on which they are adsorbed. The
225C     parameterization has been taken from studies on Th
226C     ------------------------------------------------------------
227C
228         xkeq=fekeq(ji,jj,jk)
229         xfeequi=(-(1.+fesatur(ji,jj,jk)*xkeq-xkeq*trn(ji,jj,jk,jpfer))+
230     &     sqrt((1.+fesatur(ji,jj,jk)*xkeq-xkeq*trn(ji,jj,jk,jpfer))**2
231     &     +4.*trn(ji,jj,jk,jpfer)*xkeq))/(2.*xkeq)
232
[772]233#if ! defined key_kriest
[186]234         xlam1b=3E-5+xlam1*(trn(ji,jj,jk,jppoc)
235     &     +trn(ji,jj,jk,jpgoc)+trn(ji,jj,jk,jpcal)+
236     &      trn(ji,jj,jk,jpdsi))*1E6
[617]237#else
238         xlam1b=3E-5+xlam1*(trn(ji,jj,jk,jppoc)
239     &     +trn(ji,jj,jk,jpcal)+trn(ji,jj,jk,jpdsi))*1E6
240#endif
[339]241         xscave(ji,jj,jk)=xfeequi*xlam1b*zstep
[186]242#    if defined key_off_degrad
243     &     *facvol(ji,jj,jk)
244#    endif
245C
246C  Increased scavenging for very high iron concentrations
247C  found near the coasts due to increased lithogenic particles
248C  and let's say it unknown processes (precipitation, ...)
249C  -----------------------------------------------------------
250C
[339]251         zlamfac=max(0.,(gphit(ji,jj)+55.)/30.)
252         zlamfac=min(1.,zlamfac)
[772]253#if ! defined key_kriest
[725]254         xlam1b=(80.*(trn(ji,jj,jk,jpdoc)+35E-6)+698.
[339]255     &    *trn(ji,jj,jk,jppoc)+1.05E4*trn(ji,jj,jk,jpgoc))
[725]256     &    *zdiss(ji,jj,jk)+1E-4*(1.-zlamfac)+xlam1*max(0.,
[339]257     &    (trn(ji,jj,jk,jpfer)*1E9-1.))
[617]258#else
[725]259         xlam1b=(80.*(trn(ji,jj,jk,jpdoc)+35E-6)+698.
[617]260     &    *trn(ji,jj,jk,jppoc))
[725]261     &    *zdiss(ji,jj,jk)+1E-4*(1.-zlamfac)+xlam1*max(0.,
[617]262     &    (trn(ji,jj,jk,jpfer)*1E9-1.))
263#endif
[339]264
[617]265
[725]266         xaggdfe(ji,jj,jk)=xlam1b*zstep*0.5*(trn(ji,jj,jk,jpfer)
[339]267     &     -xfeequi)
[186]268#    if defined key_off_degrad
269     &     *facvol(ji,jj,jk)
270#    endif
[339]271
[186]272C
273             END DO
274           END DO
275         END DO
276C
277#endif
278      RETURN
279      END
Note: See TracBrowser for help on using the repository browser.