/[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.12 - (hide annotations) (download)
Tue Nov 28 21:16:03 2006 UTC (17 years, 6 months ago) by stephd
Branch: MAIN
Changes since 1.11: +3 -3 lines
o changes to make dic code more adjoint friendly:
      - standardize how tracers are passed from dic_biotic_forcing to
        other subroutines
      - add a tanh function to take the place of min(x,y) in bio_export.F
        and fe_chem.F.

1 stephd 1.12 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_biotic_forcing.F,v 1.11 2005/12/16 21:07:53 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     & PTR_DOP, PTR_O2,
13     #ifdef ALLOW_FE
14     & PTR_FE,
15     #endif
16     & bi,bj,imin,imax,jmin,jmax,
17     & myIter,myTime,myThid)
18    
19 stephd 1.6 C !DESCRIPTION:
20     C updates all the tracers for the effects of air-sea exchange, biological
21     c activity and remineralization
22    
23     C !USES: ===============================================================
24 stephd 1.1 IMPLICIT NONE
25     #include "SIZE.h"
26     #include "DYNVARS.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30     #include "DIC_BIOTIC.h"
31     #include "DIC_ABIOTIC.h"
32    
33 stephd 1.6 C !INPUT PARAMETERS: ===================================================
34     C myThid :: thread number
35     C myIter :: current timestep
36     C myTime :: current time
37     C PTR_DIC :: dissolced inorganic carbon
38     C PTR_ALK :: alkalinity
39     C PTR_PO4 :: phosphate
40     c PTR_DOP :: dissolve organic phosphurous
41     c PTR_O2 :: oxygen
42     C PTR_FE :: iron
43 stephd 1.1 INTEGER myIter
44     _RL myTime
45     INTEGER myThid
46     _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47     _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
48     _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
49     _RL PTR_DOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
50     _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51     #ifdef ALLOW_FE
52     _RL PTR_FE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
53     #endif
54     INTEGER bi, bj, imin, imax, jmin, jmax
55    
56     #ifdef ALLOW_PTRACERS
57     #ifdef DIC_BIOTIC
58 stephd 1.6
59     C !LOCAL VARIABLES: ====================================================
60     C i,j,k :: loop indices
61     C G* :: tendency term for the tracers
62     C SURA :: tendency of alkalinity due to freshwater
63     C SURC :: tendency of DIC due to air-sea exchange
64     C and virtual flux
65     C SURO :: tendency of O2 due to air-sea exchange
66     C BIO :: tendency of PO4 due to biological productivity,
67     C exchange with DOP pool and reminerization
68     C CAR :: carbonate changes due to biological
69     C productivity and reminerization
70     C bioac :: biological productivity
71     C pflux :: changes to PO4 due to flux and reminerlization
72     c cflux :: carbonate changes due to flux and reminerlization
73     c freefe :: iron not bound to ligand
74 stephd 1.1 _RL GDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
75     _RL GALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
76     _RL GPO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
77     _RL GDOP(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
78     _RL GO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
79     _RL SURA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     _RL SURC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81     _RL SURO(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82     _RL BIO(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
83 stephd 1.8 _RL BIO_kar(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
84 stephd 1.1 _RL CAR(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
85     _RL bioac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
86     _RL pflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
87     _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
88     #ifdef ALLOW_FE
89     _RL GFE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90     _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
91     #endif
92     INTEGER I,J,k
93 stephd 1.8 INTEGER nCALCITEstep
94 stephd 1.6 CEOP
95 stephd 1.11 jmin=1
96     jmax=sNy
97     imin=1
98     imax=sNx
99 stephd 1.1
100     DO k=1,Nr
101     DO j=1-OLy,sNy+OLy
102     DO i=1-OLx,sNx+OLx
103     GDIC(i,j,k)=0.d0
104     GALK(i,j,k)=0.d0
105     GPO4(i,j,k)=0.d0
106     GDOP(i,j,k)=0.d0
107     GO2(i,j,k)=0.d0
108     SURA(i,j)=0.d0
109     SURC(i,j)=0.d0
110     CAR(i,j,k)=0.d0
111     BIO(i,j,k)=0.d0
112 stephd 1.8 BIO_kar(i,j,k)=0.d0
113 stephd 1.1 bioac(i,j,k)=0.d0
114     pflux(i,j,k)=0.d0
115     cflux(i,j,k)=0.d0
116     #ifdef ALLOW_FE
117     GFE(i,j,k)=0.d0
118     freefe(i,j,k)=0.d0
119     #endif
120     ENDDO
121     ENDDO
122     ENDDO
123    
124     c carbon air-sea interaction
125 stephd 1.12 CALL DIC_SURFFORCING( PTR_DIC, PTR_ALK, PTR_PO4, SURC,
126 stephd 1.1 & bi,bj,imin,imax,jmin,jmax,
127     & myIter,myTime,myThid)
128    
129     c alkalinity air-sea interaction
130     CALL ALK_SURFFORCING( PTR_ALK, SURA,
131     & bi,bj,imin,imax,jmin,jmax,
132     & myIter,myTime,myThid)
133    
134     c carbon air-sea interaction
135     CALL O2_SURFFORCING( PTR_O2, SURO,
136     & bi,bj,imin,imax,jmin,jmax,
137     & myIter,myTime,myThid)
138    
139     #ifdef ALLOW_FE
140     c find free iron
141     call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
142     & myIter, mythid)
143     #endif
144    
145    
146     c biological activity
147     CALL BIO_EXPORT( PTR_PO4 ,
148     #ifdef ALLOW_FE
149     I PTR_FE,
150     #endif
151     I bioac,
152     I bi,bj,imin,imax,jmin,jmax,
153     I myIter,myTime,myThid)
154    
155     c flux of po4 from layers with biological activity
156     CALL PHOS_FLUX( bioac, pflux,
157     & bi,bj,imin,imax,jmin,jmax,
158     & myIter,myTime,myThid)
159    
160     c carbonate
161 stephd 1.8 #ifdef CAR_DISS
162     c dissolution only below saturation horizon
163     c code following methid by Karsten Friis
164     nCALCITEstep = 3600
165     IF(myIter .lt. (nIter0+5) .or.
166     & mod(myIter,nCALCITEstep) .eq. 0)THEN
167 stephd 1.12 CALL CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
168 stephd 1.8 I bi,bj,imin,imax,jmin,jmax,
169     I myIter,myTime,myThid)
170     ENDIF
171     c
172     CALL CAR_FLUX_OMEGA_TOP( bioac, cflux,
173     & bi,bj,imin,imax,jmin,jmax,
174     & myIter,myTime,myThid)
175     #else
176     c old OCMIP way
177 stephd 1.1 CALL CAR_FLUX( bioac, cflux,
178     & bi,bj,imin,imax,jmin,jmax,
179     & myIter,myTime,myThid)
180 stephd 1.8 #endif
181 stephd 1.1
182     c add all tendencies for PO4, DOP, ALK, DIC
183     DO k=1,Nr
184 stephd 1.11 DO j=jmin,jmax
185     DO i=imin,imax
186 stephd 1.1 bio(i,j,k)=-bioac(i,j,k)+pflux(i,j,k)
187     & + maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
188     car(i,j,k)=-bioac(i,j,k)* R_cp*rain_ratio(i,j,bi,bj)*
189     & (1.0-DOPfraction)+cflux(i,j,k)
190     GPO4(i,j,k)=bio(i,j,k)
191     GDOP(i,j,k)=+bioac(i,j,k)*DOPfraction
192     & - maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
193     GALK(i,j,k)=+2.d0*car(i,j,k)-R_NP*bio(i,j,k)
194 stephd 1.8 BIO_kar(i,j,k)=R_NP*bio(i,j,k)
195 stephd 1.1 GDIC(i,j,k)=car(i,j,k)+R_CP*bio(i,j,k)
196     if (PTR_O2(i,j,k).gt.o2crit) then
197     GO2(i,j,k)=R_OP*bio(i,j,k)
198     else
199     GO2(i,j,k)=0.d0
200     endif
201     #ifdef ALLOW_FE
202     GFE(i,j,k)=R_FeP*bio(i,j,k)
203     & -Kscav*freefe(i,j,k)
204     #endif
205     IF (K.eq.1) then
206     GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
207     GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
208     GO2(i,j,1)=GO2(i,j,1)+SURO(i,j)
209     #ifdef ALLOW_FE
210     GFE(i,j,1)=GFE(i,j,1)+alpfe*
211 stephd 1.9 & InputFe(i,j,bi,bj)*recip_drF(1)
212     & *recip_hFacC(i,j,1,bi,bj)
213 stephd 1.1 #endif
214     ENDIF
215     ENDDO
216     ENDDO
217     ENDDO
218    
219    
220     C update
221     DO k=1,Nr
222 stephd 1.11 DO j=jmin,jmax
223     DO i=imin,imax
224 stephd 1.1 PTR_DIC(i,j,k)=
225 jmc 1.7 & PTR_DIC(i,j,k)+GDIC(i,j,k)*dTtracerLev(k)
226 stephd 1.1 PTR_ALK(i,j,k)=
227 jmc 1.7 & PTR_ALK(i,j,k)+GALK(i,j,k)*dTtracerLev(k)
228 stephd 1.1 PTR_PO4(i,j,k)=
229 jmc 1.7 & PTR_PO4(i,j,k)+GPO4(i,j,k)*dTtracerLev(k)
230 stephd 1.1 PTR_DOP(i,j,k)=
231 jmc 1.7 & PTR_DOP(i,j,k)+GDOP(i,j,k)*dTtracerLev(k)
232 stephd 1.1 PTR_O2(i,j,k)=
233 jmc 1.7 & PTR_O2(i,j,k)+GO2(i,j,k)*dTtracerLev(k)
234 stephd 1.1 #ifdef ALLOW_FE
235     PTR_FE(i,j,k)=
236 jmc 1.7 & PTR_FE(i,j,k)+GFE(i,j,k)*dTtracerLev(k)
237 stephd 1.1 #endif
238     ENDDO
239     ENDDO
240     ENDDO
241    
242 stephd 1.10 #ifdef ALLOW_FE
243     #ifdef MINFE
244     c find free iron and get rid of insoluble part
245     call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
246     & myIter, mythid)
247     #endif
248     #endif
249    
250    
251 stephd 1.1 #ifdef ALLOW_TIMEAVE
252     c save averages
253     DO k=1,Nr
254 stephd 1.11 DO j=jmin,jmax
255     DO i=imin,imax
256 stephd 1.1 BIOave(i,j,k,bi,bj)=BIOave(i,j,k,bi,bj)+
257     & BIOac(i,j,k)*deltaTclock
258     CARave(i,j,k,bi,bj)=CARave(i,j,k,bi,bj)+
259     & CAR(i,j,k)*deltaTclock
260 stephd 1.8 OmegaCave(i,j,k,bi,bj)= OmegaCave(i,j,k,bi,bj)+
261     & OmegaC(i,j,k,bi,bj)*deltaTclock
262     pfluxave(i,j,k,bi,bj)= pfluxave(i,j,k,bi,bj) +
263     & pflux(i,j,k)*deltaTclock
264     cfluxave(i,j,k,bi,bj)= cfluxave(i,j,k,bi,bj) +
265     & cflux(i,j,k)*deltaTclock
266 stephd 1.1 if (k.eq.1) then
267     SURave(i,j,bi,bj)=SURave(i,j,bi,bj)+
268     & SURC(i,j)*deltaTclock
269     SUROave(i,j,bi,bj)=SUROave(i,j,bi,bj)+
270     & SURO(i,j)*deltaTclock
271     pCO2ave(i,j,bi,bj)=pCO2ave(i,j,bi,bj)+
272     & pCO2(i,j,bi,bj)*deltaTclock
273     pHave(i,j,bi,bj)=pHave(i,j,bi,bj)+
274     & pH(i,j,bi,bj)*deltaTclock
275 stephd 1.2 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
276     & fluxCO2(i,j,bi,bj)*deltaTclock
277 stephd 1.1 endif
278     ENDDO
279     ENDDO
280     ENDDO
281     do k=1,Nr
282     dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)+deltaTclock
283     enddo
284     #endif
285    
286     #endif
287     #endif
288    
289     c
290     RETURN
291     END

  ViewVC Help
Powered by ViewVC 1.1.22