/[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.9 - (hide annotations) (download)
Fri Dec 16 21:07:53 2005 UTC (18 years, 6 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58n_post, checkpoint58h_post, checkpoint58j_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.8: +5 -5 lines
o dic code now does no calculations on the overlap regions

1 stephd 1.9 C $Header: /u/gcmpack/MITgcm/pkg/dic/o2_surfforcing.F,v 1.8 2005/12/12 19:07:36 stephd 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 jmc 1.6 #include "PTRACERS_SIZE.h"
29 stephd 1.1 #include "PTRACERS.h"
30     #endif
31    
32    
33 stephd 1.4 c !INPUT PARAMETERS: ===================================================
34     C myThid :: thread number
35     C myIter :: current timestep
36     C myTime :: current time
37     C PTR_O2 :: oxygen tracer field
38 stephd 1.1 _RL myTime
39     _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
40     INTEGER iMin,iMax,jMin,jMax, bi, bj
41 stephd 1.5 INTEGER myIter, myThid
42 stephd 1.1
43 stephd 1.4 c !OUTPUT PARAMETERS: ===================================================
44 stephd 1.5 C SGO2 :: air-sea exchange of oxygen
45     _RL SGO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 stephd 1.4
47 stephd 1.1 #ifdef ALLOW_PTRACERS
48    
49    
50 stephd 1.4 C !LOCAL VARIABLES: ===================================================
51 stephd 1.1 C I, J, K - Loop counters
52     INTEGER I,J,K
53     C Solubility relation coefficients
54     _RL SchmidtNoO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55     _RL O2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56     _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57     _RL FluxO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58     _RL AtmosO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59     _RL aTT
60     _RL aTK
61     _RL aTS
62     _RL aTS2
63     _RL aTS3
64     _RL aTS4
65     _RL aTS5
66     _RL o2s
67     _RL ttemp
68     _RL stemp
69     _RL oCnew
70 stephd 1.4 CEOP
71 stephd 1.1
72    
73     K=1
74    
75     C calculate SCHMIDT NO. for O2
76 stephd 1.9 DO j=jmin,jmax
77     DO i=imin,imax
78 stephd 1.1 IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
79     SchmidtNoO2(i,j) =
80     & sox1
81     & + sox2 * theta(i,j,k,bi,bj)
82     & + sox3 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
83     & + sox4 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
84     & *theta(i,j,k,bi,bj)
85    
86     C Determine surface flux of O2
87     C exchange coeff, accounting for ice cover and Schmidt no.
88     Kwexch(i,j) =
89     & pisvel(i,j,bi,bj)
90     & / sqrt(SchmidtNoO2(i,j)/660.0)
91     c ice influence
92 stephd 1.7 Kwexch(i,j) =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j)
93 stephd 1.1
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-ttemp
99     aTK = 273.15+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*1000.0
115    
116     c Determine flux, inc. correction for local atmos surface pressure
117     cQQ PTR_O2?
118     FluxO2(i,j) = maskC(i,j,k,bi,bj)*Kwexch(i,j)*
119     & (atmosP(i,j,bi,bj)*O2sat(i,j)
120     & - PTR_O2(i,j,1))
121     ELSE
122     FluxO2(i,j) = 0.d0
123     ENDIF
124    
125    
126     END DO
127     END DO
128    
129     C update surface tendencies
130 stephd 1.9 DO j=jmin,jmax
131     DO i=imin,imax
132 stephd 1.7 SGO2(i,j)= maskC(i,j,1,bi,bj)*FluxO2(i,j)
133     & *recip_drF(1) * recip_hFacC(i,j,1,bi,bj)
134 stephd 1.1 ENDDO
135     ENDDO
136     #endif
137    
138    
139     RETURN
140     END
141    

  ViewVC Help
Powered by ViewVC 1.1.22