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

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

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


Revision 1.2 - (hide annotations) (download)
Mon Sep 12 20:00:28 2016 UTC (7 years, 8 months ago) by mmazloff
Branch: MAIN
CVS Tags: checkpoint65z
Changes since 1.1: +15 -5 lines
Cleaned version of the code.

1 mmazloff 1.2 C $Header: /u/gcmpack/MITgcm/pkg/bling/bling_airseaflux.F,v 1.1 2016/05/19 20:29:26 mmazloff Exp $
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     I PTR_DIC, PTR_ALK, PTR_O2, PTR_NO3, PTR_PO4,
10     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 mmazloff 1.2 C | Adapted from pkg/dic/dic_surfforcing.F
18 mmazloff 1.1 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 mmazloff 1.2 C | - Update pCO2 and pH
23 mmazloff 1.1 C =================================================================
24    
25     implicit none
26    
27     C === Global variables ===
28     #include "SIZE.h"
29     #include "DYNVARS.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "GRID.h"
33     #include "FFIELDS.h"
34     #include "BLING_VARS.h"
35     #ifdef ALLOW_EXF
36     # include "EXF_FIELDS.h"
37     #endif
38     #ifdef ALLOW_AUTODIFF
39     # include "tamc.h"
40     #endif
41    
42     C === Routine arguments ===
43     C myTime :: current time
44     C myIter :: current timestep
45     C myThid :: thread Id. number
46     _RL myTime
47     INTEGER myIter
48     INTEGER myThid
49     INTEGER iMin, iMax, jMin, jMax, bi, bj
50     C === Input ===
51     C PTR_DIC :: DIC tracer field
52     C PTR_ALK :: alkalinity tracer field
53     C PTR_NO3 :: nitrate tracer field
54     C PTR_PO4 :: phosphate tracer field
55     C PTR_O2 :: oxygen tracer field
56     _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
57     _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58     _RL PTR_NO3(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
59     _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
60     _RL PTR_O2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
61     C === Output ===
62     C SGDIC :: tendency of DIC due to air-sea exchange
63     C SGO2 :: tendency od O2 due to air-sea exchange
64     _RL SGDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65     _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66    
67    
68     #ifdef ALLOW_PTRACERS
69    
70     C === Local variables ===
71     C i,j :: Loop counters
72     INTEGER i,j,klev
73     C Number of iterations for pCO2 solvers
74     _RL co3dummy
75     _RL Kwexch_Pre (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76     C Solubility relation coefficients
77     _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78     _RL pCO2sat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79     _RL Kwexch (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     _RL pisvel (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81     C local variables for carbon chem
82     _RL surfalk (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83     _RL surfphos (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84     _RL surfsi (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85     _RL surftemp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86     _RL surfsalt (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     _RL surfdic (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88     C o2 solubility relation coefficients
89     _RL SchmidtNoO2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90     _RL O2sat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91     _RL Kwexch_o2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92     _RL FluxO2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93     _RL aTT
94     _RL aTK
95     _RL aTS
96     _RL aTS2
97     _RL aTS3
98     _RL aTS4
99     _RL aTS5
100     _RL o2s
101     _RL ttemp
102     _RL stemp
103     _RL oCnew
104     CEOP
105    
106     C----------------------------------------------------------------------
107     C First, carbon
108     C----------------------------------------------------------------------
109     klev=1
110     C determine inorganic carbon chem coefficients
111     DO j=jmin,jmax
112     DO i=imin,imax
113    
114     surfalk(i,j) = PTR_ALK(i,j,1)
115     & * maskC(i,j,1,bi,bj)
116     surfphos(i,j) = PTR_PO4(i,j,1)
117     & * maskC(i,j,1,bi,bj)
118    
119     C FOR NON-INTERACTIVE Si
120     surfsi(i,j) = SILICA(i,j,bi,bj) * maskC(i,j,1,bi,bj)
121     surftemp(i,j) = theta(i,j,1,bi,bj)
122     surfsalt(i,j) = salt(i,j,1,bi,bj)
123     surfdic(i,j) = PTR_DIC(i,j,1)
124    
125     ENDDO
126     ENDDO
127    
128     CALL CARBON_COEFFS(
129     I surftemp,surfsalt,
130     I bi,bj,iMin,iMax,jMin,jMax,myThid)
131    
132     DO j=jmin,jmax
133     DO i=imin,imax
134     C Compute Kwexch_Pre which is re-used for flux of O2
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     pisvel(i,j) = 0.337 _d 0 * wind(i,j,bi,bj)**2/3.6 _d 5
144     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    
177     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     #ifdef USE_EXFCO2
196     pCO2sat(i,j) = apco2(i,j,bi,bj)
197     #else
198     pCO2sat(i,j) = bling_pCO2
199     #endif
200    
201     c Correct for atmospheric pressure
202 mmazloff 1.2 #ifdef USE_EXF_ATMPRES
203     C Atm pressure in N/m2, convert to bars
204     pCO2sat(i,j) = pCO2sat(i,j)*(apressure(i,j,bi,bj)*0.00001)
205     #else
206 mmazloff 1.1 pCO2sat(i,j) = pCO2sat(i,j)*AtmosP(i,j,bi,bj)
207 mmazloff 1.2 #endif
208 mmazloff 1.1
209     C then account for Schmidt number
210     Kwexch(i,j) = Kwexch_Pre(i,j)
211     & / sqrt(SchmidtNoDIC(i,j)/660.0 _d 0)
212    
213     C Calculate flux in terms of DIC units using K0, solubility
214     c Flux = kw*rho*(ff*pCO2atm-k0*FugFac*pCO2ocean)
215     FluxCO2(i,j,bi,bj) =
216     & Kwexch(i,j)*(
217     & ff(i,j,bi,bj)*pCO2sat(i,j) -
218     & pCO2(i,j,bi,bj)*fugf(i,j,bi,bj)
219     & *ak0(i,j,bi,bj) )
220     &
221     ELSE
222     FluxCO2(i,j,bi,bj) = 0. _d 0
223     ENDIF
224    
225     C convert flux (mol kg-1 m s-1) to (mol m-2 s-1)
226     FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil
227    
228     ENDDO
229     ENDDO
230    
231     C update tendency
232     DO j=jmin,jmax
233     DO i=imin,imax
234     SGDIC(i,j)= recip_drF(1)*recip_hFacC(i,j,1,bi,bj)
235     & *FluxCO2(i,j,bi,bj)
236     ENDDO
237     ENDDO
238    
239     C----------------------------------------------------------------------
240     C Now oxygen
241     C----------------------------------------------------------------------
242    
243     C calculate SCHMIDT NO. for O2
244     DO j=jmin,jmax
245     DO i=imin,imax
246     IF (maskC(i,j,1,bi,bj).NE.0.) THEN
247     ttemp = theta(i,j,1,bi,bj)
248     stemp = salt(i,j,1,bi,bj)
249    
250     SchmidtNoO2(i,j) =
251     & sox1
252     & + sox2 * ttemp
253     & + sox3 * ttemp*ttemp
254     & + sox4 * ttemp*ttemp*ttemp
255    
256     C Determine surface flux of O2
257     C exchange coeff accounting for ice cover and Schmidt no.
258     C Kwexch_Pre= pisvel*(1-fice): previously computed above
259    
260     Kwexch_o2(i,j) = Kwexch_Pre(i,j)
261     & / sqrt(SchmidtNoO2(i,j)/660.0 _d 0)
262    
263     C determine saturation O2
264     C using Garcia and Gordon (1992), L&O (mistake in original ?)
265     aTT = 298.15 _d 0 -ttemp
266     aTK = 273.15 _d 0 +ttemp
267     aTS = log(aTT/aTK)
268     aTS2 = aTS*aTS
269     aTS3 = aTS2*aTS
270     aTS4 = aTS3*aTS
271     aTS5 = aTS4*aTS
272    
273     oCnew = oA0 + oA1*aTS + oA2*aTS2 + oA3*aTS3 +
274     & oA4*aTS4 + oA5*aTS5
275     & + stemp*(oB0 + oB1*aTS + oB2*aTS2 + oB3*aTS3)
276     & + oC0*(stemp*stemp)
277    
278     o2s = EXP(oCnew)
279    
280     c Convert from ml/l to mol/m^3
281     O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
282    
283     C Determine flux, inc. correction for local atmos surface pressure
284 mmazloff 1.2 #ifdef USE_EXF_ATMPRES
285     C Atm pressure in N/m2, convert to bars
286     FluxO2(i,j) = Kwexch_o2(i,j)*(
287     & (apressure(i,j,bi,bj)*0.00001)
288     & *O2sat(i,j) - PTR_O2(i,j,1) )
289     #else
290 mmazloff 1.1 FluxO2(i,j) = Kwexch_o2(i,j)*
291     & (AtmosP(i,j,bi,bj)*O2sat(i,j)
292     & - PTR_O2(i,j,1))
293 mmazloff 1.2 #endif
294 mmazloff 1.1 ELSE
295     FluxO2(i,j) = 0. _d 0
296     ENDIF
297    
298     ENDDO
299     ENDDO
300    
301     C update surface tendencies
302     DO j=jmin,jmax
303     DO i=imin,imax
304     SGO2(i,j)= FluxO2(i,j)
305     & *recip_drF(1) * recip_hFacC(i,j,1,bi,bj)
306     ENDDO
307     ENDDO
308    
309     _EXCH_XY_RL( pCO2, mythid)
310     _EXCH_XYZ_RL( pH, mythid)
311    
312     #endif /* ALLOW_PTRACER */
313    
314     RETURN
315     END

  ViewVC Help
Powered by ViewVC 1.1.22