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

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

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


Revision 1.15 - (show annotations) (download)
Tue Aug 14 19:32:40 2007 UTC (16 years, 10 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint59f
Changes since 1.14: +12 -11 lines
- dic_fields_load.F: remove exchanges, reorder IFs and DOs, remove limit on FIce.
- remove useless loading of pLoad in o2_surfforcing.F

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/o2_surfforcing.F,v 1.14 2007/08/13 02:29:40 dfer Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5 #include "GCHEM_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: O2_SURFFORCING
9
10 C !INTERFACE: ==========================================================
11 SUBROUTINE O2_SURFFORCING( PTR_O2, SGO2,
12 I bi,bj,iMin,iMax,jMin,jMax,
13 I myIter, myTime, myThid )
14
15 C !DESCRIPTION:
16 C Calculate the oxygen air-sea flux terms
17
18 C !USES: ===============================================================
19 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 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 _RL myTime
37 _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38 INTEGER iMin,iMax,jMin,jMax, bi, bj
39 INTEGER myIter, myThid
40
41 c !OUTPUT PARAMETERS: ===================================================
42 C SGO2 :: air-sea exchange of oxygen
43 _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44
45 #ifdef ALLOW_PTRACERS
46
47 #ifdef ALLOW_O2
48
49 C !LOCAL VARIABLES: ===================================================
50 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 CEOP
70
71
72 K=1
73
74 C calculate SCHMIDT NO. for O2
75 DO j=jmin,jmax
76 DO i=imin,imax
77 IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
78 SchmidtNoO2(i,j) =
79 & sox1
80 & + sox2 * theta(i,j,k,bi,bj)
81 & + sox3 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
82 & + sox4 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
83 & *theta(i,j,k,bi,bj)
84
85 C Determine surface flux of O2
86 C exchange coeff, accounting for ice cover and Schmidt no.
87 pisvel(i,j,bi,bj)=0.337 _d 0 *wind(i,j,bi,bj)**2/3.6 _d 5
88 Kwexch(i,j) =
89 & pisvel(i,j,bi,bj)
90 & / sqrt(SchmidtNoO2(i,j)/660.0 _d 0)
91 c ice influence
92 Kwexch(i,j) =(1. _d 0 - FIce(i,j,bi,bj))*Kwexch(i,j)
93
94 ttemp = theta(i,j,k,bi,bj)
95 stemp = salt(i,j,k,bi,bj)
96 C determine saturation O2
97 C using Garcia and Gordon (1992), L&O (mistake in original???)
98 aTT = 298.15 _d 0 -ttemp
99 aTK = 273.15 _d 0 +ttemp
100 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 O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
115
116 cdfer AtmosP already computed in dic_surfforcing.F
117 C#ifdef USE_PLOAD
118 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 C AtmosP(i,j,bi,bj)= 1. _d 0 + pLoad(i,j,bi,bj)/Pa2Atm
124 C#endif
125
126 c Determine flux, inc. correction for local atmos surface pressure
127 cQQ PTR_O2?
128 FluxO2(i,j) = maskC(i,j,k,bi,bj)*Kwexch(i,j)*
129 & (AtmosP(i,j,bi,bj)*O2sat(i,j)
130 & - PTR_O2(i,j,1))
131 ELSE
132 FluxO2(i,j) = 0. _d 0
133 ENDIF
134
135
136 END DO
137 END DO
138
139 C update surface tendencies
140 DO j=jmin,jmax
141 DO i=imin,imax
142 SGO2(i,j)= maskC(i,j,1,bi,bj)*FluxO2(i,j)
143 & *recip_drF(1) * recip_hFacC(i,j,1,bi,bj)
144 ENDDO
145 ENDDO
146 #endif
147 #endif
148
149
150 RETURN
151 END
152

  ViewVC Help
Powered by ViewVC 1.1.22