/[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.17 - (show annotations) (download)
Fri Oct 26 21:08:13 2007 UTC (16 years, 7 months ago) by dfer
Branch: MAIN
Changes since 1.16: +3 -3 lines
Add tons of "_d 0" (which changes the outputs)

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

  ViewVC Help
Powered by ViewVC 1.1.22