/[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.10 - (hide annotations) (download)
Thu Oct 13 16:25:12 2005 UTC (18 years, 7 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint57v_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57x_post, checkpoint57w_post
Changes since 1.9: +10 -1 lines
o add additional switches MINFE - to limit amount of free iron
                          READ_PAR - reads PAR from file, rather
                             than using insol.F

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

  ViewVC Help
Powered by ViewVC 1.1.22