/[MITgcm]/MITgcm/pkg/dic/o2_surfforcing.F
ViewVC logotype

Annotation of /MITgcm/pkg/dic/o2_surfforcing.F

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


Revision 1.16 - (hide annotations) (download)
Mon Aug 27 18:54:47 2007 UTC (16 years, 9 months ago) by dfer
Branch: MAIN
Changes since 1.15: +12 -12 lines
-remove computation of pisvel (already done in dic_surfforcing.f)
-remove multiple use of maskC

1 dfer 1.16 C $Header: /u/gcmpack/MITgcm/pkg/dic/o2_surfforcing.F,v 1.15 2007/08/14 19:32:40 dfer Exp $
2 jmc 1.6 C $Name: $
3    
4 edhill 1.3 #include "DIC_OPTIONS.h"
5 stephd 1.1 #include "GCHEM_OPTIONS.h"
6    
7 stephd 1.4 CBOP
8     C !ROUTINE: O2_SURFFORCING
9    
10     C !INTERFACE: ==========================================================
11 stephd 1.5 SUBROUTINE O2_SURFFORCING( PTR_O2, SGO2,
12 stephd 1.1 I bi,bj,iMin,iMax,jMin,jMax,
13     I myIter, myTime, myThid )
14 stephd 1.4
15     C !DESCRIPTION:
16     C Calculate the oxygen air-sea flux terms
17    
18     C !USES: ===============================================================
19 stephd 1.1 IMPLICIT NONE
20     #include "SIZE.h"
21     #include "DYNVARS.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "GRID.h"
25     #include "FFIELDS.h"
26     #ifdef DIC_BIOTIC
27     #include "DIC_ABIOTIC.h"
28     #endif
29    
30    
31 stephd 1.4 c !INPUT PARAMETERS: ===================================================
32     C myThid :: thread number
33     C myIter :: current timestep
34     C myTime :: current time
35     C PTR_O2 :: oxygen tracer field
36 stephd 1.1 _RL myTime
37     _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38     INTEGER iMin,iMax,jMin,jMax, bi, bj
39 stephd 1.5 INTEGER myIter, myThid
40 stephd 1.1
41 stephd 1.4 c !OUTPUT PARAMETERS: ===================================================
42 stephd 1.5 C SGO2 :: air-sea exchange of oxygen
43     _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44 stephd 1.4
45 stephd 1.1 #ifdef ALLOW_PTRACERS
46    
47 stephd 1.12 #ifdef ALLOW_O2
48 stephd 1.1
49 stephd 1.4 C !LOCAL VARIABLES: ===================================================
50 stephd 1.1 C I, J, K - Loop counters
51     INTEGER I,J,K
52     C Solubility relation coefficients
53     _RL SchmidtNoO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54     _RL O2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55     _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56     _RL FluxO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57     _RL AtmosO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58     _RL aTT
59     _RL aTK
60     _RL aTS
61     _RL aTS2
62     _RL aTS3
63     _RL aTS4
64     _RL aTS5
65     _RL o2s
66     _RL ttemp
67     _RL stemp
68     _RL oCnew
69 stephd 1.4 CEOP
70 stephd 1.1
71    
72     K=1
73    
74     C calculate SCHMIDT NO. for O2
75 stephd 1.9 DO j=jmin,jmax
76     DO i=imin,imax
77 dfer 1.16 IF (maskC(i,j,k,bi,bj).NE.0.) THEN
78     ttemp = theta(i,j,k,bi,bj)
79     stemp = salt(i,j,k,bi,bj)
80    
81 stephd 1.1 SchmidtNoO2(i,j) =
82     & sox1
83 dfer 1.16 & + sox2 * ttemp
84     & + sox3 * ttemp*ttemp
85     & + sox4 * ttemp*ttemp*ttemp
86 stephd 1.1
87     C Determine surface flux of O2
88     C exchange coeff, accounting for ice cover and Schmidt no.
89 dfer 1.16 C pisvel: previously computed in dic_surfforcing.F
90 stephd 1.1 Kwexch(i,j) =
91     & pisvel(i,j,bi,bj)
92 dfer 1.15 & / sqrt(SchmidtNoO2(i,j)/660.0 _d 0)
93 stephd 1.1 c ice influence
94 dfer 1.15 Kwexch(i,j) =(1. _d 0 - FIce(i,j,bi,bj))*Kwexch(i,j)
95 stephd 1.1
96     C determine saturation O2
97     C using Garcia and Gordon (1992), L&O (mistake in original???)
98 dfer 1.15 aTT = 298.15 _d 0 -ttemp
99     aTK = 273.15 _d 0 +ttemp
100 stephd 1.1 aTS = log(aTT/aTK)
101     aTS2 = aTS*aTS
102     aTS3 = aTS2*aTS
103     aTS4 = aTS3*aTS
104     aTS5 = aTS4*aTS
105    
106     oCnew = oA0 + oA1*aTS + oA2*aTS2 + oA3*aTS3 +
107     & oA4*aTS4 + oA5*aTS5
108     & + stemp*(oB0 + oB1*aTS + oB2*aTS2 + oB3*aTS3)
109     & + oC0*(stemp*stemp)
110    
111     o2s = EXP(oCnew)
112    
113     c Convert from ml/l to mol/m^3
114 dfer 1.15 O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
115 stephd 1.1
116 dfer 1.15 cdfer AtmosP already computed in dic_surfforcing.F
117     C#ifdef USE_PLOAD
118 dfer 1.14 C Convert anomalous pressure pLoad (in Pa) from atmospheric model
119     C to total pressure (in Atm)
120     C Note: it is assumed the reference atmospheric pressure is 1Atm=1013mb
121     C rather than the actual ref. pressure from Atm. model so that on
122     C average AtmosP is about 1 Atm.
123 dfer 1.15 C AtmosP(i,j,bi,bj)= 1. _d 0 + pLoad(i,j,bi,bj)/Pa2Atm
124     C#endif
125 stephd 1.13
126 stephd 1.1 c Determine flux, inc. correction for local atmos surface pressure
127     cQQ PTR_O2?
128 dfer 1.16 FluxO2(i,j) = Kwexch(i,j)*
129 stephd 1.13 & (AtmosP(i,j,bi,bj)*O2sat(i,j)
130 stephd 1.1 & - PTR_O2(i,j,1))
131     ELSE
132 dfer 1.15 FluxO2(i,j) = 0. _d 0
133 stephd 1.1 ENDIF
134    
135    
136     END DO
137     END DO
138    
139     C update surface tendencies
140 stephd 1.9 DO j=jmin,jmax
141     DO i=imin,imax
142 dfer 1.16 SGO2(i,j)= FluxO2(i,j)
143     & *recip_drF(K) * recip_hFacC(i,j,K,bi,bj)
144 stephd 1.1 ENDDO
145     ENDDO
146     #endif
147 stephd 1.12 #endif
148 stephd 1.1
149    
150     RETURN
151     END
152    

  ViewVC Help
Powered by ViewVC 1.1.22