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

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

CL + CE : NEMO TRC_SRC start

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