/[MITgcm]/MITgcm/pkg/dic/dic_biotic_forcing.F
ViewVC logotype

Contents of /MITgcm/pkg/dic/dic_biotic_forcing.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.28 - (show annotations) (download)
Wed Aug 22 00:40:56 2012 UTC (11 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint65b, checkpoint65c, checkpoint65a
Changes since 1.27: +19 -18 lines
move full initialisation of freefe array from dic_biotic_forcing.F to fe_chem.F:
 - more logical (output arg. array of S/R FE_CHEM is defined everywhere)
 - prevents TAF to drop the initialisation in TLM code

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_forcing.F,v 1.27 2012/06/02 20:42:11 dfer Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIC_BIOTIC_FORCING
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE DIC_BIOTIC_FORCING( PTR_DIC, PTR_ALK, PTR_PO4,
11 & PTR_DOP,
12 #ifdef ALLOW_O2
13 & PTR_O2,
14 #endif
15 #ifdef ALLOW_FE
16 & PTR_FE,
17 #endif
18 & bi,bj,imin,imax,jmin,jmax,
19 & myIter,myTime,myThid)
20
21 C !DESCRIPTION:
22 C updates all the tracers for the effects of air-sea exchange, biological
23 c activity and remineralization
24
25 C !USES: ===============================================================
26 IMPLICIT NONE
27 #include "SIZE.h"
28 #include "DYNVARS.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "DIC_VARS.h"
33 #include "PTRACERS_SIZE.h"
34 #include "PTRACERS_PARAMS.h"
35
36 C !INPUT PARAMETERS: ===================================================
37 C myThid :: thread number
38 C myIter :: current timestep
39 C myTime :: current time
40 C PTR_DIC :: dissolced inorganic carbon
41 C PTR_ALK :: alkalinity
42 C PTR_PO4 :: phosphate
43 c PTR_DOP :: dissolve organic phosphurous
44 c PTR_O2 :: oxygen
45 C PTR_FE :: iron
46 INTEGER myIter
47 _RL myTime
48 INTEGER myThid
49 _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
50 _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51 _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
52 _RL PTR_DOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
53 #ifdef ALLOW_O2
54 _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
55 #endif
56 #ifdef ALLOW_FE
57 _RL PTR_FE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58 #endif
59 INTEGER bi, bj, imin, imax, jmin, jmax
60
61 #ifdef ALLOW_PTRACERS
62 #ifdef DIC_BIOTIC
63
64 C !LOCAL VARIABLES: ====================================================
65 C i,j,k :: loop indices
66 C G* :: tendency term for the tracers
67 C SURA :: tendency of alkalinity due to freshwater
68 C SURC :: tendency of DIC due to air-sea exchange
69 C and virtual flux
70 C SURO :: tendency of O2 due to air-sea exchange
71 C GPO4 :: tendency of PO4 due to biological productivity,
72 C exchange with DOP pool and reminerization
73 C CAR :: carbonate changes due to biological
74 C productivity and remineralization
75 C BIOac :: biological productivity
76 C RDOP :: DOP sink due to remineralization
77 C pflux :: changes to PO4 due to flux and remineralization
78 C CAR_S :: carbonate sink
79 C cflux :: carbonate changes due to flux and remineralization
80 C freefe :: iron not bound to ligand
81 _RL GDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
82 _RL GALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
83 _RL GPO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
84 _RL GDOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
85 _RL SURA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86 _RL SURC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87 _RL SURO(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 _RL CAR(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
89 _RL BIOac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90 _RL RDOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
91 _RL pflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
92 _RL exportflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
93 _RL CAR_S(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
94 _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
95 #ifdef ALLOW_O2
96 _RL GO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
97 #endif
98 #ifdef ALLOW_FE
99 _RL GFE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
100 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
101 #endif
102 INTEGER i,j,k
103 #ifdef CAR_DISS
104 INTEGER nCALCITEstep
105 #endif
106 CEOP
107
108 DO k=1,Nr
109 DO j=1-OLy,sNy+OLy
110 DO i=1-OLx,sNx+OLx
111 RDOP(i,j,k) =0. _d 0
112 GDIC(i,j,k) =0. _d 0
113 GALK(i,j,k) =0. _d 0
114 GPO4(i,j,k) =0. _d 0
115 GDOP(i,j,k) =0. _d 0
116 CAR(i,j,k) =0. _d 0
117 BIOac(i,j,k) =0. _d 0
118 pflux(i,j,k) =0. _d 0
119 exportflux(i,j,k)=0. _d 0
120 cflux(i,j,k) =0. _d 0
121 CAR_S(i,j,k) =0. _d 0
122 #ifdef ALLOW_O2
123 GO2(i,j,k) =0. _d 0
124 #endif
125 #ifdef ALLOW_FE
126 GFE(i,j,k) =0. _d 0
127 C no longer needed after adding full initialisation of freefe in S/R FE_CHEM
128 c freefe(i,j,k) =0. _d 0
129 #endif
130 ENDDO
131 ENDDO
132 ENDDO
133 DO j=1-OLy,sNy+OLy
134 DO i=1-OLx,sNx+OLx
135 SURA(i,j) =0. _d 0
136 SURC(i,j) =0. _d 0
137 SURO(i,j) =0. _d 0
138 ENDDO
139 ENDDO
140
141 C carbon air-sea interaction
142 CALL DIC_SURFFORCING( PTR_DIC, PTR_ALK, PTR_PO4, SURC,
143 & bi,bj,imin,imax,jmin,jmax,
144 & myIter,myTime,myThid)
145
146 C alkalinity air-sea interaction
147 CALL ALK_SURFFORCING( PTR_ALK, SURA,
148 & bi,bj,imin,imax,jmin,jmax,
149 & myIter,myTime,myThid)
150
151 #ifdef ALLOW_O2
152 C oxygen air-sea interaction
153 CALL O2_SURFFORCING( PTR_O2, SURO,
154 & bi,bj,imin,imax,jmin,jmax,
155 & myIter,myTime,myThid)
156 #endif
157
158 #ifdef ALLOW_FE
159 C find free iron
160 CALL FE_CHEM( bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
161 & myIter, myThid )
162 #endif
163
164
165 C biological activity
166 CALL BIO_EXPORT( PTR_PO4 ,
167 #ifdef ALLOW_FE
168 I PTR_FE,
169 #endif
170 I BIOac,
171 I bi,bj,imin,imax,jmin,jmax,
172 I myIter,myTime,myThid)
173
174 C flux of po4 from layers with biological activity
175 CALL PHOS_FLUX( BIOac, pflux, exportflux,
176 & bi,bj,imin,imax,jmin,jmax,
177 & myIter,myTime,myThid)
178
179 C- Carbonate sink
180 DO k=1,Nr
181 DO j=jmin,jmax
182 DO i=imin,imax
183 CAR_S(i,j,k)=BIOac(i,j,k)*R_CP*rain_ratio(i,j,bi,bj)*
184 & (1. _d 0-DOPfraction)
185 ENDDO
186 ENDDO
187 ENDDO
188
189 C carbonate
190 #ifdef CAR_DISS
191 C dissolution only below saturation horizon
192 C code following method by Karsten Friis
193 nCALCITEstep = 3600
194 IF(myIter .lt. (nIter0+5) .or.
195 & mod(myIter,nCALCITEstep) .eq. 0)THEN
196 CALL CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
197 I bi,bj,imin,imax,jmin,jmax,
198 I myIter,myTime,myThid)
199 ENDIF
200 c
201 CALL CAR_FLUX_OMEGA_TOP( BIOac, cflux,
202 & bi,bj,imin,imax,jmin,jmax,
203 & myIter,myTime,myThid)
204 #else
205 C old OCMIP way
206 CALL CAR_FLUX( CAR_S, cflux,
207 & bi,bj,imin,imax,jmin,jmax,
208 & myIter,myTime,myThid)
209 #endif
210
211 C add all tendencies for PO4, DOP, ALK, DIC
212 DO k=1,Nr
213 DO j=jmin,jmax
214 DO i=imin,imax
215 #ifdef DIC_NO_NEG
216 RDOP(i,j,k)= MAX(maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
217 & ,0. _d 0)
218 #else
219 RDOP(i,j,k)= maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
220 #endif
221 GPO4(i,j,k)=-BIOac(i,j,k)+pflux(i,j,k) + RDOP(i,j,k)
222
223 car(i,j,k) = cflux(i,j,k) - CAR_S(i,j,k)
224
225 GDOP(i,j,k)=+BIOac(i,j,k)*DOPfraction - RDOP(i,j,k)
226
227 GALK(i,j,k)=+2. _d 0 *car(i,j,k)-R_NP*GPO4(i,j,k)
228
229 GDIC(i,j,k)=car(i,j,k)+R_CP*GPO4(i,j,k)
230
231 #ifdef ALLOW_O2
232 if (PTR_O2(i,j,k).GT.O2crit) then
233 GO2(i,j,k)= R_OP*GPO4(i,j,k)
234 else
235 GO2(i,j,k)= 0. _d 0
236 endif
237 #endif
238 #ifdef ALLOW_FE
239 GFE(i,j,k) = R_FeP*GPO4(i,j,k)
240 & -Kscav*freefe(i,j,k)
241 #endif
242 ENDDO
243 ENDDO
244 ENDDO
245
246 DO j=jmin,jmax
247 DO i=imin,imax
248 GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
249 GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
250 #ifdef ALLOW_O2
251 GO2(i,j,1) =GO2(i,j,1)+SURO(i,j)
252 #endif
253 #ifdef ALLOW_FE
254 GFE(i,j,1)=GFE(i,j,1)+alpfe*
255 & InputFe(i,j,bi,bj)*recip_drF(1)
256 & *recip_hFacC(i,j,1,bi,bj)
257 #endif
258 ENDDO
259 ENDDO
260
261
262 C update
263 DO k=1,Nr
264 DO j=jmin,jmax
265 DO i=imin,imax
266 PTR_DIC(i,j,k)=
267 & PTR_DIC(i,j,k)+GDIC(i,j,k)*PTRACERS_dTLev(k)
268 PTR_ALK(i,j,k)=
269 & PTR_ALK(i,j,k)+GALK(i,j,k)*PTRACERS_dTLev(k)
270 PTR_PO4(i,j,k)=
271 & PTR_PO4(i,j,k)+GPO4(i,j,k)*PTRACERS_dTLev(k)
272 PTR_DOP(i,j,k)=
273 & PTR_DOP(i,j,k)+GDOP(i,j,k)*PTRACERS_dTLev(k)
274 #ifdef ALLOW_O2
275 PTR_O2(i,j,k)=
276 & PTR_O2(i,j,k)+GO2(i,j,k)*PTRACERS_dTLev(k)
277 #endif
278 #ifdef ALLOW_FE
279 PTR_FE(i,j,k)=
280 & PTR_FE(i,j,k)+GFE(i,j,k)*PTRACERS_dTLev(k)
281 #endif
282 ENDDO
283 ENDDO
284 ENDDO
285
286 #ifdef ALLOW_FE
287 #ifdef MINFE
288 c find free iron and get rid of insoluble part
289 CALL FE_CHEM( bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
290 & myIter, myThid )
291 #endif
292 #endif
293
294
295 #ifdef ALLOW_TIMEAVE
296 C save averages
297 IF ( PTRACERS_taveFreq.GT.0. ) THEN
298 DO k=1,Nr
299 DO j=jmin,jmax
300 DO i=imin,imax
301 BIOave(i,j,k,bi,bj) =BIOave(i,j,k,bi,bj)+
302 & BIOac(i,j,k)*deltaTClock
303 CARave(i,j,k,bi,bj) =CARave(i,j,k,bi,bj)+
304 & CAR(i,j,k)*deltaTClock
305 OmegaCave(i,j,k,bi,bj)=OmegaCave(i,j,k,bi,bj)+
306 & OmegaC(i,j,k,bi,bj)*deltaTClock
307 pfluxave(i,j,k,bi,bj) =pfluxave(i,j,k,bi,bj) +
308 & pflux(i,j,k)*deltaTClock
309 epfluxave(i,j,k,bi,bj)=epfluxave(i,j,k,bi,bj) +
310 & exportflux(i,j,k)*deltaTClock
311 cfluxave(i,j,k,bi,bj) =cfluxave(i,j,k,bi,bj) +
312 & cflux(i,j,k)*deltaTClock
313 ENDDO
314 ENDDO
315 ENDDO
316 DO j=jmin,jmax
317 DO i=imin,imax
318 SURave(i,j,bi,bj) =SURave(i,j,bi,bj)+
319 & SURC(i,j)*deltaTClock
320 #ifdef ALLOW_O2
321 SUROave(i,j,bi,bj) =SUROave(i,j,bi,bj)+
322 & SURO(i,j)*deltaTClock
323 #endif
324 pCO2ave(i,j,bi,bj) =pCO2ave(i,j,bi,bj)+
325 & pCO2(i,j,bi,bj)*deltaTClock
326 pHave(i,j,bi,bj) =pHave(i,j,bi,bj)+
327 & pH(i,j,bi,bj)*deltaTClock
328 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
329 & fluxCO2(i,j,bi,bj)*deltaTClock
330 ENDDO
331 ENDDO
332 DIC_timeAve(bi,bj) = DIC_timeAve(bi,bj)+deltaTClock
333 ENDIF
334 #endif /* ALLOW_TIMEAVE*/
335
336 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
337
338 #ifdef ALLOW_DIAGNOSTICS
339
340 IF ( useDiagnostics ) THEN
341
342 CALL DIAGNOSTICS_FILL(BIOac ,'DICBIOA ',0,Nr,2,bi,bj,myThid)
343 CALL DIAGNOSTICS_FILL(CAR ,'DICCARB ',0,Nr,2,bi,bj,myThid)
344 CALL DIAGNOSTICS_FILL(pCO2 ,'DICPCO2 ',0,1 ,1,bi,bj,myThid)
345 CALL DIAGNOSTICS_FILL(fluxCO2,'DICCFLX ',0,1 ,1,bi,bj,myThid)
346 CALL DIAGNOSTICS_FILL(pH ,'DICPHAV ',0,1 ,1,bi,bj,myThid)
347 CALL DIAGNOSTICS_FILL(SURC ,'DICTFLX ',0,1 ,2,bi,bj,myThid)
348 #ifdef ALLOW_O2
349 CALL DIAGNOSTICS_FILL(SURO ,'DICOFLX ',0,1 ,2,bi,bj,myThid)
350 #endif
351
352 ENDIF
353
354 #endif /* ALLOW_DIAGNOSTICS */
355
356 #endif /* DIC_BIOTIC */
357 #endif /* ALLOW_PTRACERS */
358
359 RETURN
360 END

  ViewVC Help
Powered by ViewVC 1.1.22