/[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.26 - (show annotations) (download)
Fri Oct 7 21:36:39 2011 UTC (12 years, 7 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g
Changes since 1.25: +2 -2 lines
Remove subroutine CALC_PCO2_APPROX_CO3 from carbon_chem.F
and add carbonate computation/output to CALC_PCO2_APPROX

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_forcing.F,v 1.25 2010/01/02 22:59:16 jmc 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 freefe(i,j,k) =0. _d 0
128 #endif
129 ENDDO
130 ENDDO
131 ENDDO
132 DO j=1-OLy,sNy+OLy
133 DO i=1-OLx,sNx+OLx
134 SURA(i,j) =0. _d 0
135 SURC(i,j) =0. _d 0
136 SURO(i,j) =0. _d 0
137 ENDDO
138 ENDDO
139
140 C carbon air-sea interaction
141 CALL DIC_SURFFORCING( PTR_DIC, PTR_ALK, PTR_PO4, SURC,
142 & bi,bj,imin,imax,jmin,jmax,
143 & myIter,myTime,myThid)
144
145 C alkalinity air-sea interaction
146 CALL ALK_SURFFORCING( PTR_ALK, SURA,
147 & bi,bj,imin,imax,jmin,jmax,
148 & myIter,myTime,myThid)
149
150 #ifdef ALLOW_O2
151 C oxygen air-sea interaction
152 CALL O2_SURFFORCING( PTR_O2, SURO,
153 & bi,bj,imin,imax,jmin,jmax,
154 & myIter,myTime,myThid)
155 #endif
156
157 #ifdef ALLOW_FE
158 C find free iron
159 CALL FE_CHEM(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
160 & myIter, mythid)
161 #endif
162
163
164 C biological activity
165 CALL BIO_EXPORT( PTR_PO4 ,
166 #ifdef ALLOW_FE
167 I PTR_FE,
168 #endif
169 I BIOac,
170 I bi,bj,imin,imax,jmin,jmax,
171 I myIter,myTime,myThid)
172
173 C flux of po4 from layers with biological activity
174 CALL PHOS_FLUX( BIOac, pflux, exportflux,
175 & bi,bj,imin,imax,jmin,jmax,
176 & myIter,myTime,myThid)
177
178 C- Carbonate sink
179 DO k=1,Nr
180 DO j=jmin,jmax
181 DO i=imin,imax
182 CAR_S(i,j,k)=BIOac(i,j,k)*R_CP*rain_ratio(i,j,bi,bj)*
183 & (1. _d 0-DOPfraction)
184 ENDDO
185 ENDDO
186 ENDDO
187
188 C carbonate
189 #ifdef CAR_DISS
190 C dissolution only below saturation horizon
191 C code following method by Karsten Friis
192 nCALCITEstep = 3600
193 IF(myIter .lt. (nIter0+5) .or.
194 & mod(myIter,nCALCITEstep) .eq. 0)THEN
195 CALL CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
196 I bi,bj,imin,imax,jmin,jmax,
197 I myIter,myTime,myThid)
198 ENDIF
199 c
200 CALL CAR_FLUX_OMEGA_TOP( BIOac, cflux,
201 & bi,bj,imin,imax,jmin,jmax,
202 & myIter,myTime,myThid)
203 #else
204 C old OCMIP way
205 CALL CAR_FLUX( CAR_S, cflux,
206 & bi,bj,imin,imax,jmin,jmax,
207 & myIter,myTime,myThid)
208 #endif
209
210 C add all tendencies for PO4, DOP, ALK, DIC
211 DO k=1,Nr
212 DO j=jmin,jmax
213 DO i=imin,imax
214 #ifdef DIC_NO_NEG
215 RDOP(i,j,k)= MAX(maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
216 & ,0. _d 0)
217 #else
218 RDOP(i,j,k)= maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
219 #endif
220 GPO4(i,j,k)=-BIOac(i,j,k)+pflux(i,j,k) + RDOP(i,j,k)
221
222 car(i,j,k) = cflux(i,j,k) - CAR_S(i,j,k)
223
224 GDOP(i,j,k)=+BIOac(i,j,k)*DOPfraction - RDOP(i,j,k)
225
226 GALK(i,j,k)=+2. _d 0 *car(i,j,k)-R_NP*GPO4(i,j,k)
227
228 GDIC(i,j,k)=car(i,j,k)+R_CP*GPO4(i,j,k)
229
230 #ifdef ALLOW_O2
231 if (PTR_O2(i,j,k).GT.O2crit) then
232 GO2(i,j,k)= R_OP*GPO4(i,j,k)
233 else
234 GO2(i,j,k)= 0. _d 0
235 endif
236 #endif
237 #ifdef ALLOW_FE
238 GFE(i,j,k) = R_FeP*GPO4(i,j,k)
239 & -Kscav*freefe(i,j,k)
240 #endif
241 ENDDO
242 ENDDO
243 ENDDO
244
245 DO j=jmin,jmax
246 DO i=imin,imax
247 GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
248 GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
249 #ifdef ALLOW_O2
250 GO2(i,j,1) =GO2(i,j,1)+SURO(i,j)
251 #endif
252 #ifdef ALLOW_FE
253 GFE(i,j,1)=GFE(i,j,1)+alpfe*
254 & InputFe(i,j,bi,bj)*recip_drF(1)
255 & *recip_hFacC(i,j,1,bi,bj)
256 #endif
257 ENDDO
258 ENDDO
259
260
261 C update
262 DO k=1,Nr
263 DO j=jmin,jmax
264 DO i=imin,imax
265 PTR_DIC(i,j,k)=
266 & PTR_DIC(i,j,k)+GDIC(i,j,k)*PTRACERS_dTLev(k)
267 PTR_ALK(i,j,k)=
268 & PTR_ALK(i,j,k)+GALK(i,j,k)*PTRACERS_dTLev(k)
269 PTR_PO4(i,j,k)=
270 & PTR_PO4(i,j,k)+GPO4(i,j,k)*PTRACERS_dTLev(k)
271 PTR_DOP(i,j,k)=
272 & PTR_DOP(i,j,k)+GDOP(i,j,k)*PTRACERS_dTLev(k)
273 #ifdef ALLOW_O2
274 PTR_O2(i,j,k)=
275 & PTR_O2(i,j,k)+GO2(i,j,k)*PTRACERS_dTLev(k)
276 #endif
277 #ifdef ALLOW_FE
278 PTR_FE(i,j,k)=
279 & PTR_FE(i,j,k)+GFE(i,j,k)*PTRACERS_dTLev(k)
280 #endif
281 ENDDO
282 ENDDO
283 ENDDO
284
285 #ifdef ALLOW_FE
286 #ifdef MINFE
287 c find free iron and get rid of insoluble part
288 call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
289 & myIter, mythid)
290 #endif
291 #endif
292
293
294 #ifdef ALLOW_TIMEAVE
295 C save averages
296 IF ( taveFreq.GT.0. ) THEN
297 DO k=1,Nr
298 DO j=jmin,jmax
299 DO i=imin,imax
300 BIOave(i,j,k,bi,bj) =BIOave(i,j,k,bi,bj)+
301 & BIOac(i,j,k)*deltaTclock
302 CARave(i,j,k,bi,bj) =CARave(i,j,k,bi,bj)+
303 & CAR(i,j,k)*deltaTclock
304 OmegaCave(i,j,k,bi,bj)=OmegaCave(i,j,k,bi,bj)+
305 & OmegaC(i,j,k,bi,bj)*deltaTclock
306 pfluxave(i,j,k,bi,bj) =pfluxave(i,j,k,bi,bj) +
307 & pflux(i,j,k)*deltaTclock
308 epfluxave(i,j,k,bi,bj)=epfluxave(i,j,k,bi,bj) +
309 & exportflux(i,j,k)*deltaTclock
310 cfluxave(i,j,k,bi,bj) =cfluxave(i,j,k,bi,bj) +
311 & cflux(i,j,k)*deltaTclock
312 ENDDO
313 ENDDO
314 ENDDO
315 DO j=jmin,jmax
316 DO i=imin,imax
317 SURave(i,j,bi,bj) =SURave(i,j,bi,bj)+
318 & SURC(i,j)*deltaTclock
319 #ifdef ALLOW_O2
320 SUROave(i,j,bi,bj) =SUROave(i,j,bi,bj)+
321 & SURO(i,j)*deltaTclock
322 #endif
323 pCO2ave(i,j,bi,bj) =pCO2ave(i,j,bi,bj)+
324 & pCO2(i,j,bi,bj)*deltaTclock
325 pHave(i,j,bi,bj) =pHave(i,j,bi,bj)+
326 & pH(i,j,bi,bj)*deltaTclock
327 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
328 & fluxCO2(i,j,bi,bj)*deltaTclock
329 ENDDO
330 ENDDO
331 DIC_timeAve(bi,bj) = DIC_timeAve(bi,bj)+deltaTclock
332 ENDIF
333 #endif /* ALLOW_TIMEAVE*/
334
335 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
336
337 #ifdef ALLOW_DIAGNOSTICS
338
339 IF ( useDiagnostics ) THEN
340
341 CALL DIAGNOSTICS_FILL(BIOac ,'DICBIOA ',0,Nr,2,bi,bj,myThid)
342 CALL DIAGNOSTICS_FILL(CAR ,'DICCARB ',0,Nr,2,bi,bj,myThid)
343 CALL DIAGNOSTICS_FILL(pCO2 ,'DICPCO2 ',0,1 ,1,bi,bj,myThid)
344 CALL DIAGNOSTICS_FILL(fluxCO2,'DICCFLX ',0,1 ,1,bi,bj,myThid)
345 CALL DIAGNOSTICS_FILL(pH ,'DICPHAV ',0,1 ,1,bi,bj,myThid)
346 CALL DIAGNOSTICS_FILL(SURC ,'DICTFLX ',0,1 ,2,bi,bj,myThid)
347 #ifdef ALLOW_O2
348 CALL DIAGNOSTICS_FILL(SURO ,'DICOFLX ',0,1 ,2,bi,bj,myThid)
349 #endif
350
351 ENDIF
352
353 #endif /* ALLOW_DIAGNOSTICS */
354
355 #endif /* DIC_BIOTIC */
356 #endif /* ALLOW_PTRACERS */
357
358 RETURN
359 END

  ViewVC Help
Powered by ViewVC 1.1.22