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

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

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


Revision 1.14 - (hide annotations) (download)
Tue May 1 21:45:33 2007 UTC (17 years, 1 month ago) by stephd
Branch: MAIN
CVS Tags: checkpoint59e, checkpoint59d, checkpoint59f, checkpoint59c, checkpoint59b
Changes since 1.13: +24 -5 lines
o set up so that pkg/dic can be run with only 4 tracers (ie. excluding O2),
  for better efficiency, particularly to be compatible with IGSM runs

1 stephd 1.14 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_forcing.F,v 1.13 2006/12/12 22:37:28 stephd Exp $
2 jmc 1.7 C $Name: $
3    
4 edhill 1.4 #include "DIC_OPTIONS.h"
5 stephd 1.1 #include "GCHEM_OPTIONS.h"
6    
7 stephd 1.6 CBOP
8     C !ROUTINE: DIC_BIOTIC_FORCING
9    
10     C !INTERFACE: ==========================================================
11 stephd 1.1 SUBROUTINE DIC_BIOTIC_FORCING( PTR_DIC, PTR_ALK, PTR_PO4,
12 stephd 1.14 & PTR_DOP,
13     #ifdef ALLOW_O2
14     & PTR_O2,
15     #endif
16 stephd 1.1 #ifdef ALLOW_FE
17     & PTR_FE,
18     #endif
19     & bi,bj,imin,imax,jmin,jmax,
20     & myIter,myTime,myThid)
21    
22 stephd 1.6 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 stephd 1.1 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 stephd 1.6 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 stephd 1.1 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 stephd 1.14 #ifdef ALLOW_O2
54 stephd 1.1 _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
55 stephd 1.14 #endif
56 stephd 1.1 #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 stephd 1.6
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 BIO :: 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 stephd 1.1 _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 BIO(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
87 stephd 1.8 _RL BIO_kar(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
88 stephd 1.1 _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 pflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
91 stephd 1.13 _RL exportflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
92 stephd 1.1 _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
93 stephd 1.14 #ifdef ALLOW_O2
94     _RL GO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
95     #endif
96 stephd 1.1 #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 stephd 1.8 INTEGER nCALCITEstep
102 stephd 1.6 CEOP
103 stephd 1.11 jmin=1
104     jmax=sNy
105     imin=1
106     imax=sNx
107 stephd 1.1
108     DO k=1,Nr
109     DO j=1-OLy,sNy+OLy
110     DO i=1-OLx,sNx+OLx
111     GDIC(i,j,k)=0.d0
112     GALK(i,j,k)=0.d0
113     GPO4(i,j,k)=0.d0
114     GDOP(i,j,k)=0.d0
115     SURA(i,j)=0.d0
116     SURC(i,j)=0.d0
117     CAR(i,j,k)=0.d0
118     BIO(i,j,k)=0.d0
119 stephd 1.8 BIO_kar(i,j,k)=0.d0
120 stephd 1.1 bioac(i,j,k)=0.d0
121     pflux(i,j,k)=0.d0
122 stephd 1.13 exportflux(i,j,k)=0.d0
123 stephd 1.1 cflux(i,j,k)=0.d0
124 stephd 1.14 #ifdef ALLOW_O2
125     GO2(i,j,k)=0.d0
126     #endif
127 stephd 1.1 #ifdef ALLOW_FE
128     GFE(i,j,k)=0.d0
129     freefe(i,j,k)=0.d0
130     #endif
131     ENDDO
132     ENDDO
133     ENDDO
134    
135     c carbon air-sea interaction
136 stephd 1.12 CALL DIC_SURFFORCING( PTR_DIC, PTR_ALK, PTR_PO4, SURC,
137 stephd 1.1 & bi,bj,imin,imax,jmin,jmax,
138     & myIter,myTime,myThid)
139    
140     c alkalinity air-sea interaction
141     CALL ALK_SURFFORCING( PTR_ALK, SURA,
142     & bi,bj,imin,imax,jmin,jmax,
143     & myIter,myTime,myThid)
144    
145 stephd 1.14 #ifdef ALLOW_O2
146     c oxygen air-sea interaction
147 stephd 1.1 CALL O2_SURFFORCING( PTR_O2, SURO,
148     & bi,bj,imin,imax,jmin,jmax,
149     & myIter,myTime,myThid)
150 stephd 1.14 #endif
151 stephd 1.1
152     #ifdef ALLOW_FE
153     c find free iron
154     call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
155     & myIter, mythid)
156     #endif
157    
158    
159     c biological activity
160     CALL BIO_EXPORT( PTR_PO4 ,
161     #ifdef ALLOW_FE
162     I PTR_FE,
163     #endif
164     I bioac,
165     I bi,bj,imin,imax,jmin,jmax,
166     I myIter,myTime,myThid)
167    
168     c flux of po4 from layers with biological activity
169 stephd 1.13 CALL PHOS_FLUX( bioac, pflux, exportflux,
170 stephd 1.1 & bi,bj,imin,imax,jmin,jmax,
171     & myIter,myTime,myThid)
172    
173     c carbonate
174 stephd 1.8 #ifdef CAR_DISS
175     c dissolution only below saturation horizon
176     c code following methid by Karsten Friis
177     nCALCITEstep = 3600
178     IF(myIter .lt. (nIter0+5) .or.
179     & mod(myIter,nCALCITEstep) .eq. 0)THEN
180 stephd 1.12 CALL CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
181 stephd 1.8 I bi,bj,imin,imax,jmin,jmax,
182     I myIter,myTime,myThid)
183     ENDIF
184     c
185     CALL CAR_FLUX_OMEGA_TOP( bioac, cflux,
186     & bi,bj,imin,imax,jmin,jmax,
187     & myIter,myTime,myThid)
188     #else
189     c old OCMIP way
190 stephd 1.1 CALL CAR_FLUX( bioac, cflux,
191     & bi,bj,imin,imax,jmin,jmax,
192     & myIter,myTime,myThid)
193 stephd 1.8 #endif
194 stephd 1.1
195     c add all tendencies for PO4, DOP, ALK, DIC
196     DO k=1,Nr
197 stephd 1.11 DO j=jmin,jmax
198     DO i=imin,imax
199 stephd 1.1 bio(i,j,k)=-bioac(i,j,k)+pflux(i,j,k)
200     & + maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
201     car(i,j,k)=-bioac(i,j,k)* R_cp*rain_ratio(i,j,bi,bj)*
202     & (1.0-DOPfraction)+cflux(i,j,k)
203     GPO4(i,j,k)=bio(i,j,k)
204     GDOP(i,j,k)=+bioac(i,j,k)*DOPfraction
205     & - maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
206     GALK(i,j,k)=+2.d0*car(i,j,k)-R_NP*bio(i,j,k)
207 stephd 1.8 BIO_kar(i,j,k)=R_NP*bio(i,j,k)
208 stephd 1.1 GDIC(i,j,k)=car(i,j,k)+R_CP*bio(i,j,k)
209 stephd 1.14 #ifdef ALLOW_O2
210 stephd 1.1 if (PTR_O2(i,j,k).gt.o2crit) then
211     GO2(i,j,k)=R_OP*bio(i,j,k)
212     else
213     GO2(i,j,k)=0.d0
214     endif
215 stephd 1.14 #endif
216 stephd 1.1 #ifdef ALLOW_FE
217     GFE(i,j,k)=R_FeP*bio(i,j,k)
218     & -Kscav*freefe(i,j,k)
219     #endif
220     IF (K.eq.1) then
221     GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
222     GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
223 stephd 1.14 #ifdef ALLOW_O2
224 stephd 1.1 GO2(i,j,1)=GO2(i,j,1)+SURO(i,j)
225 stephd 1.14 #endif
226 stephd 1.1 #ifdef ALLOW_FE
227     GFE(i,j,1)=GFE(i,j,1)+alpfe*
228 stephd 1.9 & InputFe(i,j,bi,bj)*recip_drF(1)
229     & *recip_hFacC(i,j,1,bi,bj)
230 stephd 1.1 #endif
231     ENDIF
232     ENDDO
233     ENDDO
234     ENDDO
235    
236    
237     C update
238     DO k=1,Nr
239 stephd 1.11 DO j=jmin,jmax
240     DO i=imin,imax
241 stephd 1.1 PTR_DIC(i,j,k)=
242 jmc 1.7 & PTR_DIC(i,j,k)+GDIC(i,j,k)*dTtracerLev(k)
243 stephd 1.1 PTR_ALK(i,j,k)=
244 jmc 1.7 & PTR_ALK(i,j,k)+GALK(i,j,k)*dTtracerLev(k)
245 stephd 1.1 PTR_PO4(i,j,k)=
246 jmc 1.7 & PTR_PO4(i,j,k)+GPO4(i,j,k)*dTtracerLev(k)
247 stephd 1.1 PTR_DOP(i,j,k)=
248 jmc 1.7 & PTR_DOP(i,j,k)+GDOP(i,j,k)*dTtracerLev(k)
249 stephd 1.14 #ifdef ALLOW_O2
250 stephd 1.1 PTR_O2(i,j,k)=
251 jmc 1.7 & PTR_O2(i,j,k)+GO2(i,j,k)*dTtracerLev(k)
252 stephd 1.14 #endif
253 stephd 1.1 #ifdef ALLOW_FE
254     PTR_FE(i,j,k)=
255 jmc 1.7 & PTR_FE(i,j,k)+GFE(i,j,k)*dTtracerLev(k)
256 stephd 1.1 #endif
257     ENDDO
258     ENDDO
259     ENDDO
260    
261 stephd 1.10 #ifdef ALLOW_FE
262     #ifdef MINFE
263     c find free iron and get rid of insoluble part
264     call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
265     & myIter, mythid)
266     #endif
267     #endif
268    
269    
270 stephd 1.1 #ifdef ALLOW_TIMEAVE
271     c save averages
272     DO k=1,Nr
273 stephd 1.11 DO j=jmin,jmax
274     DO i=imin,imax
275 stephd 1.1 BIOave(i,j,k,bi,bj)=BIOave(i,j,k,bi,bj)+
276     & BIOac(i,j,k)*deltaTclock
277     CARave(i,j,k,bi,bj)=CARave(i,j,k,bi,bj)+
278     & CAR(i,j,k)*deltaTclock
279 stephd 1.8 OmegaCave(i,j,k,bi,bj)= OmegaCave(i,j,k,bi,bj)+
280     & OmegaC(i,j,k,bi,bj)*deltaTclock
281     pfluxave(i,j,k,bi,bj)= pfluxave(i,j,k,bi,bj) +
282     & pflux(i,j,k)*deltaTclock
283 stephd 1.13 epfluxave(i,j,k,bi,bj)= epfluxave(i,j,k,bi,bj) +
284     & exportflux(i,j,k)*deltaTclock
285 stephd 1.8 cfluxave(i,j,k,bi,bj)= cfluxave(i,j,k,bi,bj) +
286     & cflux(i,j,k)*deltaTclock
287 stephd 1.1 if (k.eq.1) then
288     SURave(i,j,bi,bj)=SURave(i,j,bi,bj)+
289     & SURC(i,j)*deltaTclock
290 stephd 1.14 #ifdef ALLOW_O2
291 stephd 1.1 SUROave(i,j,bi,bj)=SUROave(i,j,bi,bj)+
292     & SURO(i,j)*deltaTclock
293 stephd 1.14 #endif
294 stephd 1.1 pCO2ave(i,j,bi,bj)=pCO2ave(i,j,bi,bj)+
295     & pCO2(i,j,bi,bj)*deltaTclock
296     pHave(i,j,bi,bj)=pHave(i,j,bi,bj)+
297     & pH(i,j,bi,bj)*deltaTclock
298 stephd 1.2 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
299     & fluxCO2(i,j,bi,bj)*deltaTclock
300 stephd 1.1 endif
301     ENDDO
302     ENDDO
303     ENDDO
304     do k=1,Nr
305     dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)+deltaTclock
306     enddo
307     #endif
308    
309     #endif
310     #endif
311    
312     c
313     RETURN
314     END

  ViewVC Help
Powered by ViewVC 1.1.22