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 trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/p4zrem.F @ 491

Last change on this file since 491 was 341, checked in by opalod, 19 years ago

nemo_v1_update_028 : CT : add missing headers

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