/[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.22 - (show annotations) (download)
Tue Apr 8 16:18:43 2008 UTC (16 years, 1 month ago) by dfer
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.21: +1 -5 lines
Removing dic_abiotic_param.F and dic_biotic_param.F to create
dic_readparms.F and get a data.dic

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_forcing.F,v 1.21 2008/04/07 20:31:16 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
34 C !INPUT PARAMETERS: ===================================================
35 C myThid :: thread number
36 C myIter :: current timestep
37 C myTime :: current time
38 C PTR_DIC :: dissolced inorganic carbon
39 C PTR_ALK :: alkalinity
40 C PTR_PO4 :: phosphate
41 c PTR_DOP :: dissolve organic phosphurous
42 c PTR_O2 :: oxygen
43 C PTR_FE :: iron
44 INTEGER myIter
45 _RL myTime
46 INTEGER myThid
47 _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
48 _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
49 _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
50 _RL PTR_DOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51 #ifdef ALLOW_O2
52 _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
53 #endif
54 #ifdef ALLOW_FE
55 _RL PTR_FE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56 #endif
57 INTEGER bi, bj, imin, imax, jmin, jmax
58
59 #ifdef ALLOW_PTRACERS
60 #ifdef DIC_BIOTIC
61
62 C !LOCAL VARIABLES: ====================================================
63 C i,j,k :: loop indices
64 C G* :: tendency term for the tracers
65 C SURA :: tendency of alkalinity due to freshwater
66 C SURC :: tendency of DIC due to air-sea exchange
67 C and virtual flux
68 C SURO :: tendency of O2 due to air-sea exchange
69 C GPO4 :: tendency of PO4 due to biological productivity,
70 C exchange with DOP pool and reminerization
71 C CAR :: carbonate changes due to biological
72 C productivity and remineralization
73 C BIOac :: biological productivity
74 C RDOP :: DOP sink due to remineralization
75 C pflux :: changes to PO4 due to flux and remineralization
76 C CAR_S :: carbonate sink
77 C cflux :: carbonate changes due to flux and remineralization
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 RDOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
89 _RL pflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90 _RL exportflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
91 _RL CAR_S(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
92 _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
93 #ifdef ALLOW_O2
94 _RL GO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
95 #endif
96 #ifdef ALLOW_FE
97 _RL GFE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
98 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
99 #endif
100 INTEGER I,J,k
101 INTEGER nCALCITEstep
102 CEOP
103
104 DO k=1,Nr
105 DO j=1-OLy,sNy+OLy
106 DO i=1-OLx,sNx+OLx
107 RDOP(i,j,k) =0. _d 0
108 GDIC(i,j,k) =0. _d 0
109 GALK(i,j,k) =0. _d 0
110 GPO4(i,j,k) =0. _d 0
111 GDOP(i,j,k) =0. _d 0
112 CAR(i,j,k) =0. _d 0
113 BIOac(i,j,k) =0. _d 0
114 pflux(i,j,k) =0. _d 0
115 exportflux(i,j,k)=0. _d 0
116 cflux(i,j,k) =0. _d 0
117 CAR_S(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 sink
175 DO k=1,Nr
176 DO j=jmin,jmax
177 DO i=imin,imax
178 CAR_S(i,j,k)=BIOac(i,j,k)*R_CP*rain_ratio(i,j,bi,bj)*
179 & (1. _d 0-DOPfraction)
180 ENDDO
181 ENDDO
182 ENDDO
183
184 c carbonate
185 #ifdef CAR_DISS
186 c dissolution only below saturation horizon
187 c code following methid by Karsten Friis
188 nCALCITEstep = 3600
189 IF(myIter .lt. (nIter0+5) .or.
190 & mod(myIter,nCALCITEstep) .eq. 0)THEN
191 CALL CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
192 I bi,bj,imin,imax,jmin,jmax,
193 I myIter,myTime,myThid)
194 ENDIF
195 c
196 CALL CAR_FLUX_OMEGA_TOP( BIOac, cflux,
197 & bi,bj,imin,imax,jmin,jmax,
198 & myIter,myTime,myThid)
199 #else
200 c old OCMIP way
201 CALL CAR_FLUX( CAR_S, cflux,
202 & bi,bj,imin,imax,jmin,jmax,
203 & myIter,myTime,myThid)
204 #endif
205
206 c add all tendencies for PO4, DOP, ALK, DIC
207 DO k=1,Nr
208 DO j=jmin,jmax
209 DO i=imin,imax
210 #ifdef DIC_NO_NEG
211 RDOP(i,j,k)= MAX(maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
212 & ,0. _d 0)
213 #else
214 RDOP(i,j,k)= maskC(i,j,k,bi,bj)*KDOPRemin*PTR_DOP(i,j,k)
215 #endif
216 GPO4(i,j,k)=-BIOac(i,j,k)+pflux(i,j,k) + RDOP(i,j,k)
217
218 car(i,j,k) = cflux(i,j,k) - CAR_S(i,j,k)
219
220 GDOP(i,j,k)=+BIOac(i,j,k)*DOPfraction - RDOP(i,j,k)
221
222 GALK(i,j,k)=+2. _d 0 *car(i,j,k)-R_NP*GPO4(i,j,k)
223
224 GDIC(i,j,k)=car(i,j,k)+R_CP*GPO4(i,j,k)
225
226 #ifdef ALLOW_O2
227 if (PTR_O2(i,j,k).GT.O2crit) then
228 GO2(i,j,k)= R_OP*GPO4(i,j,k)
229 else
230 GO2(i,j,k)= 0. _d 0
231 endif
232 #endif
233 #ifdef ALLOW_FE
234 GFE(i,j,k) = R_FeP*GPO4(i,j,k)
235 & -Kscav*freefe(i,j,k)
236 #endif
237 ENDDO
238 ENDDO
239 ENDDO
240
241 DO j=jmin,jmax
242 DO i=imin,imax
243 GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
244 GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
245 #ifdef ALLOW_O2
246 GO2(i,j,1) =GO2(i,j,1)+SURO(i,j)
247 #endif
248 #ifdef ALLOW_FE
249 GFE(i,j,1)=GFE(i,j,1)+alpfe*
250 & InputFe(i,j,bi,bj)*recip_drF(1)
251 & *recip_hFacC(i,j,1,bi,bj)
252 #endif
253 ENDDO
254 ENDDO
255
256
257 C update
258 DO k=1,Nr
259 DO j=jmin,jmax
260 DO i=imin,imax
261 PTR_DIC(i,j,k)=
262 & PTR_DIC(i,j,k)+GDIC(i,j,k)*dTtracerLev(k)
263 PTR_ALK(i,j,k)=
264 & PTR_ALK(i,j,k)+GALK(i,j,k)*dTtracerLev(k)
265 PTR_PO4(i,j,k)=
266 & PTR_PO4(i,j,k)+GPO4(i,j,k)*dTtracerLev(k)
267 PTR_DOP(i,j,k)=
268 & PTR_DOP(i,j,k)+GDOP(i,j,k)*dTtracerLev(k)
269 #ifdef ALLOW_O2
270 PTR_O2(i,j,k)=
271 & PTR_O2(i,j,k)+GO2(i,j,k)*dTtracerLev(k)
272 #endif
273 #ifdef ALLOW_FE
274 PTR_FE(i,j,k)=
275 & PTR_FE(i,j,k)+GFE(i,j,k)*dTtracerLev(k)
276 #endif
277 ENDDO
278 ENDDO
279 ENDDO
280
281 #ifdef ALLOW_FE
282 #ifdef MINFE
283 c find free iron and get rid of insoluble part
284 call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
285 & myIter, mythid)
286 #endif
287 #endif
288
289
290 #ifdef ALLOW_TIMEAVE
291 c save averages
292 IF ( taveFreq.GT.0. ) THEN
293 DO k=1,Nr
294 DO j=jmin,jmax
295 DO i=imin,imax
296 BIOave(i,j,k,bi,bj) =BIOave(i,j,k,bi,bj)+
297 & BIOac(i,j,k)*deltaTclock
298 CARave(i,j,k,bi,bj) =CARave(i,j,k,bi,bj)+
299 & CAR(i,j,k)*deltaTclock
300 OmegaCave(i,j,k,bi,bj)=OmegaCave(i,j,k,bi,bj)+
301 & OmegaC(i,j,k,bi,bj)*deltaTclock
302 pfluxave(i,j,k,bi,bj) =pfluxave(i,j,k,bi,bj) +
303 & pflux(i,j,k)*deltaTclock
304 epfluxave(i,j,k,bi,bj)=epfluxave(i,j,k,bi,bj) +
305 & exportflux(i,j,k)*deltaTclock
306 cfluxave(i,j,k,bi,bj) =cfluxave(i,j,k,bi,bj) +
307 & cflux(i,j,k)*deltaTclock
308 ENDDO
309 ENDDO
310 ENDDO
311 DO j=jmin,jmax
312 DO i=imin,imax
313 SURave(i,j,bi,bj) =SURave(i,j,bi,bj)+
314 & SURC(i,j)*deltaTclock
315 #ifdef ALLOW_O2
316 SUROave(i,j,bi,bj) =SUROave(i,j,bi,bj)+
317 & SURO(i,j)*deltaTclock
318 #endif
319 pCO2ave(i,j,bi,bj) =pCO2ave(i,j,bi,bj)+
320 & pCO2(i,j,bi,bj)*deltaTclock
321 pHave(i,j,bi,bj) =pHave(i,j,bi,bj)+
322 & pH(i,j,bi,bj)*deltaTclock
323 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
324 & fluxCO2(i,j,bi,bj)*deltaTclock
325 ENDDO
326 ENDDO
327 do k=1,Nr
328 dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)+deltaTclock
329 enddo
330 ENDIF
331 #endif /* ALLOW_TIMEAVE*/
332
333 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
334
335 #ifdef ALLOW_DIAGNOSTICS
336
337 IF ( useDiagnostics ) THEN
338
339 CALL DIAGNOSTICS_FILL(BIOac ,'DICBIOA ',0,Nr,2,bi,bj,myThid)
340 CALL DIAGNOSTICS_FILL(CAR ,'DICCARB ',0,Nr,2,bi,bj,myThid)
341 CALL DIAGNOSTICS_FILL(pCO2 ,'DICPCO2 ',0,1 ,1,bi,bj,myThid)
342 CALL DIAGNOSTICS_FILL(fluxCO2,'DICCFLX ',0,1 ,1,bi,bj,myThid)
343 CALL DIAGNOSTICS_FILL(pH ,'DICPHAV ',0,1 ,1,bi,bj,myThid)
344 CALL DIAGNOSTICS_FILL(SURC ,'DICTFLX ',0,1 ,2,bi,bj,myThid)
345 #ifdef ALLOW_O2
346 CALL DIAGNOSTICS_FILL(SURO ,'DICOFLX ',0,1 ,2,bi,bj,myThid)
347 #endif
348
349 ENDIF
350
351 #endif /* ALLOW_DIAGNOSTICS */
352
353 #endif /* DIC_BIOTIC */
354 #endif /* ALLOW_PTRACERS */
355
356 c
357 RETURN
358 END

  ViewVC Help
Powered by ViewVC 1.1.22