/[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.20 - (hide annotations) (download)
Fri Apr 4 21:37:06 2008 UTC (16 years, 2 months ago) by dfer
Branch: MAIN
Changes since 1.19: +2 -2 lines
Merging DIC_ABIOTIC.h and DIC_BIOTIC.h

1 dfer 1.20 C $Header: /u/gcmpack/MITgcm/pkg/dic/o2_surfforcing.F,v 1.19 2008/04/04 18:57:36 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 dfer 1.20 #include "DIC_VARS.h"
27 stephd 1.1
28 stephd 1.4 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 stephd 1.1 _RL myTime
34     _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
35     INTEGER iMin,iMax,jMin,jMax, bi, bj
36 stephd 1.5 INTEGER myIter, myThid
37 stephd 1.1
38 stephd 1.4 c !OUTPUT PARAMETERS: ===================================================
39 stephd 1.5 C SGO2 :: air-sea exchange of oxygen
40     _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 stephd 1.4
42 stephd 1.1 #ifdef ALLOW_PTRACERS
43    
44 stephd 1.12 #ifdef ALLOW_O2
45 stephd 1.1
46 stephd 1.4 C !LOCAL VARIABLES: ===================================================
47 stephd 1.1 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 stephd 1.4 CEOP
66 stephd 1.1
67    
68     K=1
69    
70     C calculate SCHMIDT NO. for O2
71 stephd 1.9 DO j=jmin,jmax
72     DO i=imin,imax
73 dfer 1.16 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 stephd 1.1 SchmidtNoO2(i,j) =
78     & sox1
79 dfer 1.16 & + sox2 * ttemp
80     & + sox3 * ttemp*ttemp
81     & + sox4 * ttemp*ttemp*ttemp
82 stephd 1.1
83     C Determine surface flux of O2
84 dfer 1.17 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 stephd 1.1
90     C determine saturation O2
91     C using Garcia and Gordon (1992), L&O (mistake in original???)
92 dfer 1.15 aTT = 298.15 _d 0 -ttemp
93     aTK = 273.15 _d 0 +ttemp
94 stephd 1.1 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 dfer 1.15 O2sat(i,j) = o2s/22391.6 _d 0 * 1. _d 3
109 stephd 1.1
110 dfer 1.17 C Determine flux, inc. correction for local atmos surface pressure
111 dfer 1.16 FluxO2(i,j) = Kwexch(i,j)*
112 stephd 1.13 & (AtmosP(i,j,bi,bj)*O2sat(i,j)
113 dfer 1.17 & - PTR_O2(i,j,K))
114 stephd 1.1 ELSE
115 dfer 1.15 FluxO2(i,j) = 0. _d 0
116 stephd 1.1 ENDIF
117    
118    
119     END DO
120     END DO
121    
122     C update surface tendencies
123 stephd 1.9 DO j=jmin,jmax
124     DO i=imin,imax
125 dfer 1.16 SGO2(i,j)= FluxO2(i,j)
126     & *recip_drF(K) * recip_hFacC(i,j,K,bi,bj)
127 stephd 1.1 ENDDO
128     ENDDO
129     #endif
130 stephd 1.12 #endif
131 stephd 1.1
132    
133     RETURN
134     END
135    

  ViewVC Help
Powered by ViewVC 1.1.22