/[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.19 - (show annotations) (download)
Fri Apr 4 18:57:36 2008 UTC (16 years, 2 months ago) by dfer
Branch: MAIN
Changes since 1.18: +1 -4 lines
Some fixes for the "#undef DIC_BI0TIC" case

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/o2_surfforcing.F,v 1.18 2008/02/29 22:36:13 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 #include "DIC_ABIOTIC.h"
27
28 c !INPUT PARAMETERS: ===================================================
29 C myThid :: thread number
30 C myIter :: current timestep
31 C myTime :: current time
32 C PTR_O2 :: oxygen tracer field
33 _RL myTime
34 _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
35 INTEGER iMin,iMax,jMin,jMax, bi, bj
36 INTEGER myIter, myThid
37
38 c !OUTPUT PARAMETERS: ===================================================
39 C SGO2 :: air-sea exchange of oxygen
40 _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41
42 #ifdef ALLOW_PTRACERS
43
44 #ifdef ALLOW_O2
45
46 C !LOCAL VARIABLES: ===================================================
47 C I, J, K - Loop counters
48 INTEGER I,J,K
49 C Solubility relation coefficients
50 _RL SchmidtNoO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 _RL O2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL FluxO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54 _RL aTT
55 _RL aTK
56 _RL aTS
57 _RL aTS2
58 _RL aTS3
59 _RL aTS4
60 _RL aTS5
61 _RL o2s
62 _RL ttemp
63 _RL stemp
64 _RL oCnew
65 CEOP
66
67
68 K=1
69
70 C calculate SCHMIDT NO. for O2
71 DO j=jmin,jmax
72 DO i=imin,imax
73 IF (maskC(i,j,k,bi,bj).NE.0.) THEN
74 ttemp = theta(i,j,k,bi,bj)
75 stemp = salt(i,j,k,bi,bj)
76
77 SchmidtNoO2(i,j) =
78 & sox1
79 & + sox2 * ttemp
80 & + sox3 * ttemp*ttemp
81 & + sox4 * ttemp*ttemp*ttemp
82
83 C Determine surface flux of O2
84 C exchange coeff accounting for ice cover and Schmidt no.
85 C Kwexch_Pre= pisvel*(1-fice): previously computed in dic_surfforcing.F
86
87 Kwexch(i,j) = Kwexch_Pre(i,j,bi,bj)
88 & / sqrt(SchmidtNoO2(i,j)/660.0 _d 0)
89
90 C determine saturation O2
91 C using Garcia and Gordon (1992), L&O (mistake in original???)
92 aTT = 298.15 _d 0 -ttemp
93 aTK = 273.15 _d 0 +ttemp
94 aTS = log(aTT/aTK)
95 aTS2 = aTS*aTS
96 aTS3 = aTS2*aTS
97 aTS4 = aTS3*aTS
98 aTS5 = aTS4*aTS
99
100 oCnew = oA0 + oA1*aTS + oA2*aTS2 + oA3*aTS3 +
101 & oA4*aTS4 + oA5*aTS5
102 & + stemp*(oB0 + oB1*aTS + oB2*aTS2 + oB3*aTS3)
103 & + oC0*(stemp*stemp)
104
105 o2s = EXP(oCnew)
106
107 c Convert from ml/l to mol/m^3
108 O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
109
110 C Determine flux, inc. correction for local atmos surface pressure
111 FluxO2(i,j) = Kwexch(i,j)*
112 & (AtmosP(i,j,bi,bj)*O2sat(i,j)
113 & - PTR_O2(i,j,K))
114 ELSE
115 FluxO2(i,j) = 0. _d 0
116 ENDIF
117
118
119 END DO
120 END DO
121
122 C update surface tendencies
123 DO j=jmin,jmax
124 DO i=imin,imax
125 SGO2(i,j)= FluxO2(i,j)
126 & *recip_drF(K) * recip_hFacC(i,j,K,bi,bj)
127 ENDDO
128 ENDDO
129 #endif
130 #endif
131
132
133 RETURN
134 END
135

  ViewVC Help
Powered by ViewVC 1.1.22