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

Annotation of /MITgcm/pkg/dic/dic_surfforcing.F

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


Revision 1.2 - (hide annotations) (download)
Wed Jul 9 19:59:18 2003 UTC (22 years ago) by stephd
Branch: MAIN
CVS Tags: checkpoint51e_post, checkpoint51f_pre, checkpoint51f_post, branchpoint-genmake2, checkpoint51g_post, checkpoint51d_post
Branch point for: branch-genmake2
Changes since 1.1: +7 -6 lines
add variable Si; fix bugs in dic_diags, dic_fields_load

1 stephd 1.1 #include "CPP_OPTIONS.h"
2     #include "PTRACERS_OPTIONS.h"
3     #include "GCHEM_OPTIONS.h"
4    
5     CStartOfInterFace
6     SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC,
7     I bi,bj,imin,imax,jmin,jmax,
8     I myIter,myTime,myThid)
9    
10     C /==========================================================\
11     C | SUBROUTINE DIC_SURFFORCING |
12     C | o Calculate the carbon air-sea flux terms |
13     C | o following external_forcing_dic.F from Mick |
14     C |==========================================================|
15     IMPLICIT NONE
16    
17     C == GLobal variables ==
18     #include "SIZE.h"
19     #include "DYNVARS.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "GRID.h"
23     #include "FFIELDS.h"
24     #include "DIC_ABIOTIC.h"
25     #ifdef DIC_BIOTIC
26     #include "PTRACERS.h"
27     #endif
28    
29     C == Routine arguments ==
30     INTEGER myIter, myThid
31     _RL myTime
32     _RL PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
33     _RL GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
34     INTEGER iMin,iMax,jMin,jMax, bi, bj
35    
36     #ifdef ALLOW_PTRACERS
37     #ifdef DIC_ABIOTIC
38     C == Local variables ==
39 stephd 1.2 INTEGER I,J, kLev, it
40 stephd 1.1 C Number of iterations for pCO2 solvers...
41     INTEGER inewtonmax
42     INTEGER ibrackmax
43     INTEGER donewt
44     C Solubility relation coefficients
45     _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46     _RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47     _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48     C local variables for carbon chem
49     _RL surfalk(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50     _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51     _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52     _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53    
54     cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
55    
56     kLev=1
57    
58     C PRE-INDUSTRIAL STEADY STATE pCO2 = 278.0 ppmv
59     DO j=1-OLy,sNy+OLy
60     DO i=1-OLx,sNx+OLx
61     AtmospCO2(i,j,bi,bj)=278.0d-6
62     ENDDO
63     ENDDO
64    
65    
66     C =================================================================
67     C determine inorganic carbon chem coefficients
68     DO j=1-OLy,sNy+OLy
69     DO i=1-OLx,sNx+OLx
70    
71     #ifdef DIC_BIOTIC
72     cQQQQ check ptracer numbers
73     surfalk(i,j) = PTRACER(i,j,klev,bi,bj,2)
74     & * maskC(i,j,kLev,bi,bj)
75     surfphos(i,j) = PTRACER(i,j,klev,bi,bj,3)
76     & * maskC(i,j,kLev,bi,bj)
77     #else
78     surfalk(i,j) = 2.366595 * salt(i,j,kLev,bi,bj)/gsm_s
79     & * maskC(i,j,kLev,bi,bj)
80     surfphos(i,j) = 5.1225e-4 * maskC(i,j,kLev,bi,bj)
81     #endif
82     C FOR NON-INTERACTIVE Si
83     surfsi(i,j) = 7.6838e-3 * maskC(i,j,kLev,bi,bj)
84     ENDDO
85     ENDDO
86    
87     CALL CARBON_COEFFS(
88     I theta,salt,
89     I bi,bj,iMin,iMax,jMin,jMax)
90     C====================================================================
91    
92     #define PH_APPROX
93     c set number of iterations for [H+] solvers
94     #ifdef PH_APPROX
95     inewtonmax = 1
96     #else
97     inewtonmax = 10
98     #endif
99     ibrackmax = 30
100     C determine pCO2 in surface ocean
101     C set guess of pH for first step here
102     C IF first step THEN use bracket-bisection for first step,
103     C and determine carbon coefficients for safety
104     C ELSE use newton-raphson with previous H+(x,y) as first guess
105    
106     donewt=1
107    
108     c for first few timesteps
109     IF(myIter .le. (nIter0+inewtonmax) )then
110     donewt=0
111     DO j=1-OLy,sNy+OLy
112     DO i=1-OLx,sNx+OLx
113     pH(i,j,bi,bj) = 8.0
114     ENDDO
115     ENDDO
116     #ifdef PH_APPROX
117     print*,'QQ: pCO2 approximation method'
118     c first approxmation
119     DO j=1-OLy,sNy+OLy
120     DO i=1-OLx,sNx+OLx
121 stephd 1.2 do it=1,10
122 stephd 1.1 CALL CALC_PCO2_APPROX(
123     I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj),
124     I PTR_CO2(i,j,kLev), surfphos(i,j),
125     I surfsi(i,j),surfalk(i,j),
126     I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
127     I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
128     I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
129     I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj),
130     I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
131     U pH(i,j,bi,bj),pCO2(i,j,bi,bj) )
132 stephd 1.2 enddo
133 stephd 1.1 ENDDO
134     ENDDO
135     #else
136     print*,'QQ: pCO2 full method'
137     #endif
138     ENDIF
139    
140    
141     c pCO2 solver...
142     DO j=1-OLy,sNy+OLy
143     DO i=1-OLx,sNx+OLx
144    
145     IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN
146     #ifdef PH_APPROX
147     CALL CALC_PCO2_APPROX(
148     I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj),
149     I PTR_CO2(i,j,kLev), surfphos(i,j),
150     I surfsi(i,j),surfalk(i,j),
151     I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
152     I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
153     I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
154     I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj),
155     I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
156     U pH(i,j,bi,bj),pCO2(i,j,bi,bj) )
157     #else
158     CALL CALC_PCO2(donewt,inewtonmax,ibrackmax,
159     I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj),
160     I PTR_CO2(i,j,kLev), surfphos(i,j),
161     I surfsi(i,j),surfalk(i,j),
162     I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
163     I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
164     I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
165     I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj),
166     I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
167     U pH(i,j,bi,bj),pCO2(i,j,bi,bj) )
168     #endif
169     ELSE
170     pCO2(i,j,bi,bj)=0. _d 0
171     END IF
172     ENDDO
173     ENDDO
174    
175     DO j=1-OLy,sNy+OLy
176     DO i=1-OLx,sNx+OLx
177    
178     IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN
179     C calculate SCHMIDT NO. for CO2
180     SchmidtNoDIC(i,j) =
181     & sca1
182     & + sca2 * theta(i,j,kLev,bi,bj)
183     & + sca3 * theta(i,j,kLev,bi,bj)*theta(i,j,kLev,bi,bj)
184     & + sca4 * theta(i,j,kLev,bi,bj)*theta(i,j,kLev,bi,bj)
185     & *theta(i,j,kLev,bi,bj)
186    
187     C Determine surface flux (FDIC)
188     C first correct pCO2at for surface atmos pressure
189     pCO2sat(i,j) =
190     & AtmosP(i,j,bi,bj)*AtmospCO2(i,j,bi,bj)
191     c find exchange coefficient
192     c account for schmidt number and and varible piston velocity
193     Kwexch(i,j) =
194     & pisvel(i,j,bi,bj)
195     & / sqrt(SchmidtNoDIC(i,j)/660.0)
196     c OR use a constant coeff
197     c Kwexch(i,j) = 5e-5
198     c ice influence
199     cQQ Kwexch(i,j) =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j)
200    
201    
202     C Calculate flux in terms of DIC units using K0, solubility
203     C Flux = Vp * ([CO2sat] - [CO2])
204     C CO2sat = K0*pCO2atmos*P/P0
205     C Converting pCO2 to [CO2] using ff, as in CALC_PCO2
206 stephd 1.2 FluxCO2(i,j,bi,bj) =
207 stephd 1.1 & maskC(i,j,kLev,bi,bj)*Kwexch(i,j)*(
208     & ak0(i,j,bi,bj)*pCO2sat(i,j) -
209     & ff(i,j,bi,bj)*pCO2(i,j,bi,bj)
210     & )
211     ELSE
212 stephd 1.2 FluxCO2(i,j,bi,bj) = 0.
213 stephd 1.1 ENDIF
214     C convert flux (mol kg-1 m s-1) to (mol m-2 s-1)
215 stephd 1.2 FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil
216 stephd 1.1
217     IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN
218     c calculate virtual flux
219     c EminusPforV = dS/dt*(1/Sglob)
220     C NOTE: Be very careful with signs here!
221     C Positive EminusPforV => loss of water to atmos and increase
222     C in salinity. Thus, also increase in other surface tracers
223     C (i.e. positive virtual flux into surface layer)
224     C ...so here, VirtualFLux = dC/dt!
225     VirtualFlux(i,j)=gsm_DIC*surfaceTendencyS(i,j,bi,bj)/gsm_s
226     c OR
227     c let virtual flux be zero
228     c VirtualFlux(i,j)=0.d0
229     c
230     ELSE
231     VirtualFlux(i,j)=0. _d 0
232     ENDIF
233     ENDDO
234     ENDDO
235    
236     C update tendency
237     DO j=1-OLy,sNy+OLy
238     DO i=1-OLx,sNx+OLx
239     GDC(i,j)= maskC(i,j,kLev,bi,bj)*(
240 stephd 1.2 & FluxCO2(i,j,bi,bj)*recip_drF(kLev)
241 stephd 1.1 & + VirtualFlux(i,j)
242     & )
243     ENDDO
244     ENDDO
245    
246     #endif
247     #endif
248     RETURN
249     END

  ViewVC Help
Powered by ViewVC 1.1.22