/[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.1 - (hide annotations) (download)
Wed Jun 25 21:00:36 2003 UTC (21 years ago) by stephd
Branch: MAIN
CVS Tags: checkpoint51e_post, checkpoint51a_post, checkpoint51c_post, checkpoint51f_pre, checkpoint51f_post, checkpoint51b_post, checkpoint51b_pre, branchpoint-genmake2, checkpoint51g_post, checkpoint51d_post
Branch point for: branch-genmake2
initial checking in biogeochemistry packages

1 stephd 1.1 #include "CPP_OPTIONS.h"
2     #include "GCHEM_OPTIONS.h"
3    
4     CStartOfInterFace
5     SUBROUTINE O2_SURFFORCING( PTR_O2, GO2,
6     I bi,bj,iMin,iMax,jMin,jMax,
7     I myIter, myTime, myThid )
8     C /==========================================================\
9     C | SUBROUTINE O2_SURFFORCING |
10     C | o Calculate the oxygen air-sea flux terms |
11     C | o following external_forcing_o2.F from Mick |
12     C |==========================================================|
13     IMPLICIT NONE
14    
15     C == GLobal variables ==
16     #include "SIZE.h"
17     #include "DYNVARS.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "GRID.h"
21     #include "FFIELDS.h"
22     #ifdef DIC_BIOTIC
23     #include "DIC_ABIOTIC.h"
24     #include "PTRACERS.h"
25     #endif
26    
27    
28     C == Routine arguments ==
29     INTEGER myIter, myThid
30     _RL myTime
31     _RL PTR_O2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
32     _RL GO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
33     INTEGER iMin,iMax,jMin,jMax, bi, bj
34    
35     #ifdef ALLOW_PTRACERS
36     #ifdef DIC_ABIOTIC
37    
38    
39     C == Local variables ==
40     C I, J, K - Loop counters
41     INTEGER I,J,K
42     C Solubility relation coefficients
43     _RL SchmidtNoO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44     _RL O2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45     _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46     _RL FluxO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47     _RL AtmosO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48     _RL aTT
49     _RL aTK
50     _RL aTS
51     _RL aTS2
52     _RL aTS3
53     _RL aTS4
54     _RL aTS5
55     _RL o2s
56     _RL ttemp
57     _RL stemp
58     _RL oCnew
59    
60    
61     K=1
62    
63     C calculate SCHMIDT NO. for O2
64     DO j=jMin,jMax
65     DO i=iMin,iMax
66     IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
67     SchmidtNoO2(i,j) =
68     & sox1
69     & + sox2 * theta(i,j,k,bi,bj)
70     & + sox3 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
71     & + sox4 * theta(i,j,k,bi,bj)*theta(i,j,k,bi,bj)
72     & *theta(i,j,k,bi,bj)
73    
74     C Determine surface flux of O2
75     C exchange coeff, accounting for ice cover and Schmidt no.
76     Kwexch(i,j) =
77     & pisvel(i,j,bi,bj)
78     & / sqrt(SchmidtNoO2(i,j)/660.0)
79     c ice influence
80     cQQ Kwexch(i,j) =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j)
81    
82     ttemp = theta(i,j,k,bi,bj)
83     stemp = salt(i,j,k,bi,bj)
84     C determine saturation O2
85     C using Garcia and Gordon (1992), L&O (mistake in original???)
86     aTT = 298.15-ttemp
87     aTK = 273.15+ttemp
88     aTS = log(aTT/aTK)
89     aTS2 = aTS*aTS
90     aTS3 = aTS2*aTS
91     aTS4 = aTS3*aTS
92     aTS5 = aTS4*aTS
93    
94     oCnew = oA0 + oA1*aTS + oA2*aTS2 + oA3*aTS3 +
95     & oA4*aTS4 + oA5*aTS5
96     & + stemp*(oB0 + oB1*aTS + oB2*aTS2 + oB3*aTS3)
97     & + oC0*(stemp*stemp)
98    
99     o2s = EXP(oCnew)
100    
101     c Convert from ml/l to mol/m^3
102     O2sat(i,j) = o2s/22391.6*1000.0
103    
104     c Determine flux, inc. correction for local atmos surface pressure
105     cQQ PTR_O2?
106     FluxO2(i,j) = maskC(i,j,k,bi,bj)*Kwexch(i,j)*
107     & (atmosP(i,j,bi,bj)*O2sat(i,j)
108     & - PTR_O2(i,j,1))
109     ELSE
110     FluxO2(i,j) = 0.d0
111     ENDIF
112    
113    
114     END DO
115     END DO
116    
117     C update surface tendencies
118     DO j=jMin,jMax
119     DO i=iMin,iMax
120     GO2(i,j)= maskC(i,j,1,bi,bj)*FluxO2(i,j)*recip_drF(1)
121     ENDDO
122     ENDDO
123     #endif
124     #endif
125    
126    
127     RETURN
128     END
129    

  ViewVC Help
Powered by ViewVC 1.1.22