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

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

  ViewVC Help
Powered by ViewVC 1.1.22