/[MITgcm]/MITgcm_contrib/bling/pkg/bling_airseaflux.F
ViewVC logotype

Annotation of /MITgcm_contrib/bling/pkg/bling_airseaflux.F

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


Revision 1.3 - (hide annotations) (download)
Sun Feb 28 21:49:24 2016 UTC (9 years, 4 months ago) by mmazloff
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +10 -7 lines
Update to BLING version 2

1 mmazloff 1.3 C $Header: $
2 mmazloff 1.1 C $Name: $
3    
4     #include "BLING_OPTIONS.h"
5     #include "PTRACERS_OPTIONS.h"
6    
7     CBOP
8     subroutine BLING_AIRSEAFLUX(
9 mmazloff 1.3 I PTR_DIC, PTR_ALK, PTR_O2, PTR_NO3, PTR_PO4,
10 mmazloff 1.1 O SGDIC, SGO2,
11     I bi, bj, imin, imax, jmin, jmax,
12     I myIter, myTime, myThid)
13    
14     C =================================================================
15     C | subroutine bling_airseaflux
16     C | o Calculate the carbon and oxygen air-sea flux terms
17     C | Adapted from pkg/dic/
18     C | - Get atmospheric pCO2 value
19     C | Option 1: constant value, default 268.d-6, can be changed in
20     C | data.bling
21     C | Option 2: read 2D field using EXF pkg
22     C =================================================================
23    
24     implicit none
25    
26     C === Global variables ===
27     #include "SIZE.h"
28     #include "DYNVARS.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "FFIELDS.h"
33     #include "BLING_VARS.h"
34     #ifdef ALLOW_EXF
35     # include "EXF_FIELDS.h"
36     #endif
37 mmazloff 1.3 #ifdef ALLOW_AUTODIFF
38 mmazloff 1.1 # include "tamc.h"
39     #endif
40    
41     C === Routine arguments ===
42     C myTime :: current time
43     C myIter :: current timestep
44     C myThid :: thread Id. number
45     _RL myTime
46     INTEGER myIter
47     INTEGER myThid
48     INTEGER iMin, iMax, jMin, jMax, bi, bj
49     C === Input ===
50     C PTR_DIC :: DIC tracer field
51     C PTR_ALK :: alkalinity tracer field
52 mmazloff 1.3 C PTR_NO3 :: nitrate tracer field
53     C PTR_PO4 :: phosphate tracer field
54 mmazloff 1.1 C PTR_O2 :: oxygen tracer field
55     _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56     _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
57 mmazloff 1.3 _RL PTR_NO3(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58     _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
59 mmazloff 1.1 _RL PTR_O2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
60     C === Output ===
61     C SGDIC :: tendency of DIC due to air-sea exchange
62     C SGO2 :: tendency od O2 due to air-sea exchange
63     _RL SGDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64     _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65    
66    
67     #ifdef ALLOW_PTRACERS
68    
69     C === Local variables ===
70     C i,j :: Loop counters
71     INTEGER i,j,klev
72     C Number of iterations for pCO2 solvers
73     _RL co3dummy
74     _RL Kwexch_Pre (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75     C Solubility relation coefficients
76     _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77     _RL pCO2sat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78     _RL Kwexch (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79     _RL pisvel (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     C local variables for carbon chem
81     _RL surfalk (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82     _RL surfphos (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83     _RL surfsi (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84     _RL surftemp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85     _RL surfsalt (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86     _RL surfdic (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     C o2 solubility relation coefficients
88     _RL SchmidtNoO2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89     _RL O2sat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90     _RL Kwexch_o2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91     _RL FluxO2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92     _RL aTT
93     _RL aTK
94     _RL aTS
95     _RL aTS2
96     _RL aTS3
97     _RL aTS4
98     _RL aTS5
99     _RL o2s
100     _RL ttemp
101     _RL stemp
102     _RL oCnew
103     CEOP
104    
105     C----------------------------------------------------------------------
106     C First, carbon
107     C----------------------------------------------------------------------
108     klev=1
109     C determine inorganic carbon chem coefficients
110     DO j=jmin,jmax
111     DO i=imin,imax
112    
113     surfalk(i,j) = PTR_ALK(i,j,1)
114     & * maskC(i,j,1,bi,bj)
115 mmazloff 1.3 surfphos(i,j) = PTR_PO4(i,j,1)
116 mmazloff 1.1 & * maskC(i,j,1,bi,bj)
117    
118     C FOR NON-INTERACTIVE Si
119     surfsi(i,j) = SILICA(i,j,bi,bj) * maskC(i,j,1,bi,bj)
120     surftemp(i,j) = theta(i,j,1,bi,bj)
121     surfsalt(i,j) = salt(i,j,1,bi,bj)
122     surfdic(i,j) = PTR_DIC(i,j,1)
123    
124     ENDDO
125     ENDDO
126    
127     CALL CARBON_COEFFS(
128     I surftemp,surfsalt,
129     I bi,bj,iMin,iMax,jMin,jMax,myThid)
130    
131     DO j=jmin,jmax
132     DO i=imin,imax
133     C Compute Kwexch_Pre which is re-used for flux of O2
134     caxx Atmos pressure is assumed to be 1 atm
135    
136     c Read EXF winds instead of value from file:
137     #ifdef ALLOW_EXF
138     wind(i,j,bi,bj) = wspeed(i,j,bi,bj)
139     #endif
140    
141     C Pre-compute part of exchange coefficient: pisvel*(1-fice)
142     C Schmidt number is accounted for later
143 mmazloff 1.3 pisvel(i,j) = 0.337 _d 0 * wind(i,j,bi,bj)**2/3.6 _d 5
144 mmazloff 1.1 Kwexch_Pre(i,j) = pisvel(i,j)
145     & * (1. _d 0 - FIce(i,j,bi,bj))
146    
147     ENDDO
148     ENDDO
149    
150     c pCO2 solver...
151    
152     CADJ STORE ph = comlev1, key = ikey_dynamics
153    
154     C$TAF LOOP = parallel
155     DO j=jmin,jmax
156     C$TAF LOOP = parallel
157     DO i=imin,imax
158    
159     IF ( maskC(i,j,klev,bi,bj).NE.0. _d 0 ) THEN
160     CALL CALC_PCO2_APPROX(
161     I surftemp(i,j),surfsalt(i,j),
162     I surfdic(i,j), surfphos(i,j),
163     I surfsi(i,j),surfalk(i,j),
164     I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
165     I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
166     I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
167     I aksi(i,j,bi,bj),akf(i,j,bi,bj),
168     I ak0(i,j,bi,bj), fugf(i,j,bi,bj),
169     I ff(i,j,bi,bj),
170     I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
171     U pH(i,j,klev,bi,bj),pCO2(i,j,bi,bj),co3dummy,
172     I i,j,klev,bi,bj,myIter,myThid )
173     ELSE
174     pCO2(i,j,bi,bj) = 0. _d 0
175     ENDIF
176 mmazloff 1.3
177 mmazloff 1.1 ENDDO
178     ENDDO
179    
180     DO j=jmin,jmax
181     DO i=imin,imax
182    
183     IF ( maskC(i,j,1,bi,bj).NE.0. _d 0 ) THEN
184     C calculate SCHMIDT NO. for CO2
185     SchmidtNoDIC(i,j) =
186     & sca1
187     & + sca2 * theta(i,j,1,bi,bj)
188     & + sca3 * theta(i,j,1,bi,bj)*theta(i,j,1,bi,bj)
189     & + sca4 * theta(i,j,1,bi,bj)*theta(i,j,1,bi,bj)
190     & *theta(i,j,1,bi,bj)
191     c make sure Schmidt number is not negative (will happen if temp>39C)
192     SchmidtNoDIC(i,j)=max(1.0 _d -2, SchmidtNoDIC(i,j))
193    
194     C First determine local saturation pCO2
195 mmazloff 1.2 #ifdef USE_EXFCO2
196 mmazloff 1.1 pCO2sat(i,j) = apco2(i,j,bi,bj)
197     #else
198     pCO2sat(i,j) = bling_pCO2
199     #endif
200    
201     #ifndef BLING_ADJOINT_SAFE
202     c Correct for atmospheric pressure
203     pCO2sat(i,j) = pCO2sat(i,j)*AtmosP(i,j,bi,bj)
204     #endif
205    
206     C then account for Schmidt number
207     Kwexch(i,j) = Kwexch_Pre(i,j)
208     & / sqrt(SchmidtNoDIC(i,j)/660.0 _d 0)
209    
210     C Calculate flux in terms of DIC units using K0, solubility
211     c Flux = kw*rho*(ff*pCO2atm-k0*FugFac*pCO2ocean)
212     FluxCO2(i,j,bi,bj) =
213     & Kwexch(i,j)*(
214     & ff(i,j,bi,bj)*pCO2sat(i,j) -
215     & pCO2(i,j,bi,bj)*fugf(i,j,bi,bj)
216     & *ak0(i,j,bi,bj) )
217     &
218     ELSE
219     FluxCO2(i,j,bi,bj) = 0. _d 0
220     ENDIF
221    
222     C convert flux (mol kg-1 m s-1) to (mol m-2 s-1)
223     FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil
224    
225     ENDDO
226     ENDDO
227    
228     C update tendency
229     DO j=jmin,jmax
230     DO i=imin,imax
231     SGDIC(i,j)= recip_drF(1)*recip_hFacC(i,j,1,bi,bj)
232     & *FluxCO2(i,j,bi,bj)
233     ENDDO
234     ENDDO
235    
236     C----------------------------------------------------------------------
237     C Now oxygen
238     C----------------------------------------------------------------------
239    
240     C calculate SCHMIDT NO. for O2
241     DO j=jmin,jmax
242     DO i=imin,imax
243     IF (maskC(i,j,1,bi,bj).NE.0.) THEN
244     ttemp = theta(i,j,1,bi,bj)
245     stemp = salt(i,j,1,bi,bj)
246    
247     SchmidtNoO2(i,j) =
248     & sox1
249     & + sox2 * ttemp
250     & + sox3 * ttemp*ttemp
251     & + sox4 * ttemp*ttemp*ttemp
252    
253     C Determine surface flux of O2
254     C exchange coeff accounting for ice cover and Schmidt no.
255     C Kwexch_Pre= pisvel*(1-fice): previously computed above
256    
257     Kwexch_o2(i,j) = Kwexch_Pre(i,j)
258     & / sqrt(SchmidtNoO2(i,j)/660.0 _d 0)
259    
260     C determine saturation O2
261     C using Garcia and Gordon (1992), L&O (mistake in original ?)
262     aTT = 298.15 _d 0 -ttemp
263     aTK = 273.15 _d 0 +ttemp
264     aTS = log(aTT/aTK)
265     aTS2 = aTS*aTS
266     aTS3 = aTS2*aTS
267     aTS4 = aTS3*aTS
268     aTS5 = aTS4*aTS
269    
270     oCnew = oA0 + oA1*aTS + oA2*aTS2 + oA3*aTS3 +
271     & oA4*aTS4 + oA5*aTS5
272     & + stemp*(oB0 + oB1*aTS + oB2*aTS2 + oB3*aTS3)
273     & + oC0*(stemp*stemp)
274    
275     o2s = EXP(oCnew)
276    
277     c Convert from ml/l to mol/m^3
278     O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
279    
280     C Determine flux, inc. correction for local atmos surface pressure
281     FluxO2(i,j) = Kwexch_o2(i,j)*
282     & (AtmosP(i,j,bi,bj)*O2sat(i,j)
283     & - PTR_O2(i,j,1))
284     ELSE
285     FluxO2(i,j) = 0. _d 0
286     ENDIF
287    
288     ENDDO
289     ENDDO
290    
291     C update surface tendencies
292     DO j=jmin,jmax
293     DO i=imin,imax
294     SGO2(i,j)= FluxO2(i,j)
295     & *recip_drF(1) * recip_hFacC(i,j,1,bi,bj)
296     ENDDO
297     ENDDO
298    
299     _EXCH_XY_RL( pCO2, mythid)
300     _EXCH_XYZ_RL( pH, mythid)
301    
302     #endif /* ALLOW_PTRACER */
303    
304     RETURN
305     END

  ViewVC Help
Powered by ViewVC 1.1.22