/[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.7 - (show annotations) (download)
Sat Dec 4 00:15:14 2004 UTC (19 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint57i_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57f_pre, checkpoint57a_post, checkpoint57a_pre, checkpoint57, eckpoint57e_pre, checkpoint57h_done, checkpoint57n_post, checkpoint57p_post, checkpoint57f_post, checkpoint57c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post
Changes since 1.6: +9 -6 lines
depth convergence accelerator: replace deltaTtracer by dTtracerLev(k)

1 C $Header: $
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, PTR_O2,
13 #ifdef ALLOW_FE
14 & PTR_FE,
15 #endif
16 & bi,bj,imin,imax,jmin,jmax,
17 & myIter,myTime,myThid)
18
19 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 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 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 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
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 _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 _RL CAR(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
84 _RL bioac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
85 _RL pflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
86 _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
87 #ifdef ALLOW_FE
88 _RL GFE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
89 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90 #endif
91 INTEGER I,J,k
92 CEOP
93
94 DO k=1,Nr
95 DO j=1-OLy,sNy+OLy
96 DO i=1-OLx,sNx+OLx
97 GDIC(i,j,k)=0.d0
98 GALK(i,j,k)=0.d0
99 GPO4(i,j,k)=0.d0
100 GDOP(i,j,k)=0.d0
101 GO2(i,j,k)=0.d0
102 SURA(i,j)=0.d0
103 SURC(i,j)=0.d0
104 CAR(i,j,k)=0.d0
105 BIO(i,j,k)=0.d0
106 bioac(i,j,k)=0.d0
107 pflux(i,j,k)=0.d0
108 cflux(i,j,k)=0.d0
109 #ifdef ALLOW_FE
110 GFE(i,j,k)=0.d0
111 freefe(i,j,k)=0.d0
112 #endif
113 ENDDO
114 ENDDO
115 ENDDO
116
117 c carbon air-sea interaction
118 CALL DIC_SURFFORCING( PTR_DIC, SURC,
119 & bi,bj,imin,imax,jmin,jmax,
120 & myIter,myTime,myThid)
121
122 c alkalinity air-sea interaction
123 CALL ALK_SURFFORCING( PTR_ALK, SURA,
124 & bi,bj,imin,imax,jmin,jmax,
125 & myIter,myTime,myThid)
126
127 c carbon air-sea interaction
128 CALL O2_SURFFORCING( PTR_O2, SURO,
129 & bi,bj,imin,imax,jmin,jmax,
130 & myIter,myTime,myThid)
131
132 #ifdef ALLOW_FE
133 c find free iron
134 call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
135 & myIter, mythid)
136 #endif
137
138
139 c biological activity
140 CALL BIO_EXPORT( PTR_PO4 ,
141 #ifdef ALLOW_FE
142 I PTR_FE,
143 #endif
144 I bioac,
145 I bi,bj,imin,imax,jmin,jmax,
146 I myIter,myTime,myThid)
147
148 c flux of po4 from layers with biological activity
149 CALL PHOS_FLUX( bioac, pflux,
150 & bi,bj,imin,imax,jmin,jmax,
151 & myIter,myTime,myThid)
152
153 c carbonate
154 CALL CAR_FLUX( bioac, cflux,
155 & bi,bj,imin,imax,jmin,jmax,
156 & myIter,myTime,myThid)
157
158 c add all tendencies for PO4, DOP, ALK, DIC
159 DO k=1,Nr
160 DO j=1-OLy,sNy+OLy
161 DO i=1-OLx,sNx+OLx
162 bio(i,j,k)=-bioac(i,j,k)+pflux(i,j,k)
163 & + maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
164 car(i,j,k)=-bioac(i,j,k)* R_cp*rain_ratio(i,j,bi,bj)*
165 & (1.0-DOPfraction)+cflux(i,j,k)
166 GPO4(i,j,k)=bio(i,j,k)
167 GDOP(i,j,k)=+bioac(i,j,k)*DOPfraction
168 & - maskC(i,j,k,bi,bj)*Kdopremin*PTR_DOP(i,j,k)
169 GALK(i,j,k)=+2.d0*car(i,j,k)-R_NP*bio(i,j,k)
170 GDIC(i,j,k)=car(i,j,k)+R_CP*bio(i,j,k)
171 if (PTR_O2(i,j,k).gt.o2crit) then
172 GO2(i,j,k)=R_OP*bio(i,j,k)
173 else
174 GO2(i,j,k)=0.d0
175 endif
176 #ifdef ALLOW_FE
177 GFE(i,j,k)=R_FeP*bio(i,j,k)
178 & -Kscav*freefe(i,j,k)
179 #endif
180 IF (K.eq.1) then
181 GALK(i,j,1)=GALK(i,j,1)+SURA(i,j)
182 GDIC(i,j,1)=GDIC(i,j,1)+SURC(i,j)
183 GO2(i,j,1)=GO2(i,j,1)+SURO(i,j)
184 #ifdef ALLOW_FE
185 GFE(i,j,1)=GFE(i,j,1)+alpfe*
186 & InputFe(i,j,bi,bj)/drF(1)
187 #endif
188 ENDIF
189 ENDDO
190 ENDDO
191 ENDDO
192
193
194 C update
195 DO k=1,Nr
196 DO j=1-OLy,sNy+OLy
197 DO i=1-OLx,sNx+OLx
198 PTR_DIC(i,j,k)=
199 & PTR_DIC(i,j,k)+GDIC(i,j,k)*dTtracerLev(k)
200 PTR_ALK(i,j,k)=
201 & PTR_ALK(i,j,k)+GALK(i,j,k)*dTtracerLev(k)
202 PTR_PO4(i,j,k)=
203 & PTR_PO4(i,j,k)+GPO4(i,j,k)*dTtracerLev(k)
204 PTR_DOP(i,j,k)=
205 & PTR_DOP(i,j,k)+GDOP(i,j,k)*dTtracerLev(k)
206 PTR_O2(i,j,k)=
207 & PTR_O2(i,j,k)+GO2(i,j,k)*dTtracerLev(k)
208 #ifdef ALLOW_FE
209 PTR_FE(i,j,k)=
210 & PTR_FE(i,j,k)+GFE(i,j,k)*dTtracerLev(k)
211 #endif
212 ENDDO
213 ENDDO
214 ENDDO
215
216 #ifdef ALLOW_TIMEAVE
217 c save averages
218 DO k=1,Nr
219 DO j=1-OLy,sNy+OLy
220 DO i=1-OLx,sNx+OLx
221 BIOave(i,j,k,bi,bj)=BIOave(i,j,k,bi,bj)+
222 & BIOac(i,j,k)*deltaTclock
223 CARave(i,j,k,bi,bj)=CARave(i,j,k,bi,bj)+
224 & CAR(i,j,k)*deltaTclock
225 if (k.eq.1) then
226 SURave(i,j,bi,bj)=SURave(i,j,bi,bj)+
227 & SURC(i,j)*deltaTclock
228 SUROave(i,j,bi,bj)=SUROave(i,j,bi,bj)+
229 & SURO(i,j)*deltaTclock
230 pCO2ave(i,j,bi,bj)=pCO2ave(i,j,bi,bj)+
231 & pCO2(i,j,bi,bj)*deltaTclock
232 pHave(i,j,bi,bj)=pHave(i,j,bi,bj)+
233 & pH(i,j,bi,bj)*deltaTclock
234 fluxCO2ave(i,j,bi,bj)=fluxCO2ave(i,j,bi,bj)+
235 & fluxCO2(i,j,bi,bj)*deltaTclock
236 endif
237 ENDDO
238 ENDDO
239 ENDDO
240 do k=1,Nr
241 dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)+deltaTclock
242 enddo
243 #endif
244
245 #endif
246 #endif
247
248 c
249 RETURN
250 END

  ViewVC Help
Powered by ViewVC 1.1.22