/[MITgcm]/MITgcm_contrib/dcarroll/highres_darwin/code/dic_surfforcing_init.F
ViewVC logotype

Contents of /MITgcm_contrib/dcarroll/highres_darwin/code/dic_surfforcing_init.F

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


Revision 1.1 - (show annotations) (download)
Sun Sep 22 21:23:46 2019 UTC (5 years, 10 months ago) by dcarroll
Branch: MAIN
CVS Tags: HEAD
Initial check in of high resolution Darwin simulation code

1 #include "CPP_OPTIONS.h"
2 #include "PTRACERS_OPTIONS.h"
3 #include "DARWIN_OPTIONS.h"
4
5 #ifdef ALLOW_PTRACERS
6 #ifdef ALLOW_DARWIN
7
8 #ifdef ALLOW_CARBON
9
10 CBOP
11 C !ROUTINE: DIC_SURFFORCING_INIT
12
13 C !INTERFACE: ==========================================================
14 SUBROUTINE DIC_SURFFORCING_INIT(
15 I myThid)
16
17 C !DESCRIPTION:
18 C Calculate first guess of pH
19
20 C !USES: ===============================================================
21 IMPLICIT NONE
22 #include "SIZE.h"
23 #include "DYNVARS.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "GRID.h"
27 #include "FFIELDS.h"
28 #include "PTRACERS_SIZE.h"
29 #include "PTRACERS_PARAMS.h"
30 #include "PTRACERS_FIELDS.h"
31 #include "DARWIN_SIZE.h"
32 #include "DARWIN_IO.h"
33 #include "DARWIN_FLUX.h"
34 #include "DIC_ATMOS.h"
35
36 C !INPUT PARAMETERS: ===================================================
37 C myThid :: thread number
38 INTEGER myThid
39
40
41 C !LOCAL VARIABLES: ====================================================
42 INTEGER i,j, k, kLev, it
43 INTEGER intime0,intime1
44 _RL otime
45 _RL aWght,bWght,rdt
46 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
47 C Number of iterations for pCO2 solvers...
48 C Solubility relation coefficients
49 C local variables for carbon chemCO2(i,j,bi,bj),
50 INTEGER iMin,iMax,jMin,jMax, bi, bj
51 _RL surfdic(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 _RL surfalk(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54 _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55 _RL surfsalt(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 _RL surftemp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 INTEGER iprt,jprt
58 CHARACTER*(MAX_LEN_MBUF) msgBuf
59 INTEGER iUnit
60 CHARACTER*(MAX_LEN_FNAM) iName
61 integer ilo,ihi
62 integer ilnblnk,ifnblnk
63 external ilnblnk,ifnblnk
64 LOGICAL pH_isLoaded
65 CEOP
66
67 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
68
69 kLev=1
70
71 cBX add EXF call to initialize atmospheric CO2 (otherwise a value
72 cBX of zero is carried and restart is inconsistent). As the
73 cBX loading of exf fields is done later than processing in dic
74 cBX routines time stepping needs to be shifted by one.
75 CALL EXF_GETFORCING2( startTime-deltaT, nIter0-1, myThid )
76
77 CALL DIC_ATMOS(0, startTime, nIter0, myThid )
78
79 _BEGIN_MASTER(myThid)
80
81 C set up coefficients for DIC chemistry
82 C define Schmidt no. coefficients for CO2
83 sca1 = 2073.1 _d 0
84 sca2 = -125.62 _d 0
85 sca3 = 3.6276 _d 0
86 sca4 = -0.043219 _d 0
87 C define Schmidt no. coefficients for O2
88 C based on Keeling et al [GBC, 12, 141, (1998)]
89 sox1 = 1638.0 _d 0
90 sox2 = -81.83 _d 0
91 sox3 = 1.483 _d 0
92 sox4 = -0.008004 _d 0
93
94 C coefficients for determining saturation O2
95 oA0= 2.00907 _d 0
96 oA1= 3.22014 _d 0
97 oA2= 4.05010 _d 0
98 oA3= 4.94457 _d 0
99 oA4= -2.56847 _d -1
100 oA5= 3.88767 _d 0
101 oB0= -6.24523 _d -3
102 oB1= -7.37614 _d -3
103 oB2= -1.03410 _d -2
104 oB3= -8.17083 _d -3
105 oC0= -4.88682 _d -7
106 C Set other constant/flag
107
108 #ifndef USE_ATMOSCO2
109
110 #ifndef USE_EXFCO2
111 if (dic_int1.eq.2) then
112 call mdsfindunit( iUnit, mythid )
113 open(UNIT=iUnit,FILE='co2atmos.dat',STATUS='old')
114 do k=1,dic_int2
115 read(iUnit,*) co2atmos(k)
116 print*,'co2atmos',co2atmos(k)
117 enddo
118 close(iUnit)
119 endif
120
121 if (dic_int1.eq.3) then
122 write(iName,'(A,I10.10)') 'dic_atmos.',nIter0
123 ilo = ifnblnk(iName)
124 ihi = ilnblnk(iName)
125 call mdsfindunit( iUnit, mythid )
126 open(UNIT=iUnit,FILE=iname(ilo:ihi),STATUS='old')
127 read(iUnit,*) total_atmos_carbon_ini,
128 & atpco2_ini
129 close(iUnit)
130 endif
131 #endif
132
133 #endif
134 _END_MASTER(myThid)
135
136 ccccccccccccccccccccccccccccccccccccccccc
137 IF ( periodicExternalForcing ) THEN
138
139
140 rdt = 1. _d 0 / deltaTclock
141 nForcingPeriods = NINT(externForcingCycle/externForcingPeriod)
142 cswd QQ change for placement of chem forcing (ie. after timestep)
143 Imytm = NINT(startTime*rdt)
144 Ifprd = NINT(externForcingPeriod*rdt)
145 Ifcyc = NINT(externForcingCycle*rdt)
146 Iftm = MOD( Imytm+Ifcyc-Ifprd/2, Ifcyc)
147
148 intime0 = 1 + INT(Iftm/Ifprd)
149 intime1 = 1 + MOD(intime0,nForcingPeriods)
150 c aWght = DFLOAT( Iftm-Ifprd*(intime0 - 1) ) / DFLOAT( Ifprd )
151 aWght = FLOAT( Iftm-Ifprd*(intime0 - 1) )
152 bWght = FLOAT( Ifprd )
153 aWght = aWght / bWght
154 bWght = 1. _d 0 - aWght
155
156 _BARRIER
157 _BEGIN_MASTER(myThid)
158
159 _END_MASTER(myThid)
160
161 #ifdef ALLOW_OFFLINE
162 IF ( useOffLine ) THEN
163 otime=nIter0*deltaTclock
164 CALL OFFLINE_FIELDS_LOAD( otime, nIter0, myThid )
165 ENDIF
166 #endif
167
168 c end periodicExternalForcing
169 ENDIF
170
171 C =================================================================
172
173 jMin=1
174 jMax=sNy
175 iMin=1
176 iMax=sNx
177
178 DO bj=myByLo(myThid),myByHi(myThid)
179 DO bi=myBxLo(myThid),myBxHi(myThid)
180 DO j=1-OLy,sNy+OLy
181 DO i=1-Olx,sNx+OLx
182 pH(i,j,bi,bj) = 8. _d 0
183 ENDDO
184 ENDDO
185 ENDDO
186 ENDDO
187
188 DO bj=myByLo(myThid),myByHi(myThid)
189 DO bi=myBxLo(myThid),myBxHi(myThid)
190 DO j=1-OLy,sNy+OLy
191 DO i=1-OLx,sNx+OLx
192 ak0(i,j,bi,bj)=0. _d 0
193 ak1(i,j,bi,bj)=0. _d 0
194 ak2(i,j,bi,bj)=0. _d 0
195 akw(i,j,bi,bj)=0. _d 0
196 akb(i,j,bi,bj)=0. _d 0
197 akf(i,j,bi,bj)=0. _d 0
198 ak1p(i,j,bi,bj)=0. _d 0
199 ak2p(i,j,bi,bj)=0. _d 0
200 ak3p(i,j,bi,bj)=0. _d 0
201 aksi(i,j,bi,bj)=0. _d 0
202 fugf(i,j,bi,bj)=0. _d 0
203 ff(i,j,bi,bj)=0. _d 0
204 ft(i,j,bi,bj)=0. _d 0
205 st(i,j,bi,bj)=0. _d 0
206 bt(i,j,bi,bj)=0. _d 0
207 ENDDO
208 ENDDO
209 ENDDO
210 ENDDO
211
212 pH_isLoaded = .FALSE.
213 IF ( nIter0.GT.PTRACERS_Iter0 ) THEN
214 C Read pH from a pickup file if needed
215 CALL DIC_READ_PICKUP(
216 O pH_isLoaded,
217 I nIter0, myThid )
218 ENDIF
219
220 DO bj=myByLo(myThid),myByHi(myThid)
221 DO bi=myBxLo(myThid),myBxHi(myThid)
222
223 C determine inorganic carbon chem coefficients
224 DO j=jMin,jMax
225 DO i=iMin,iMax
226
227 c use surface layer values and convert to mol/m3
228 c and put bounds on tracers so pH solver doesn't blow up
229 surfdic(i,j) =
230 & max(10. _d 0 ,
231 & min(4000. _d 0, Ptracer(i,j,1,bi,bj,iDIC)))*1e-3
232 & * maskC(i,j,kLev,bi,bj)
233 surfalk(i,j) =
234 & max(10. _d 0 ,
235 & min(4000. _d 0, Ptracer(i,j,1,bi,bj,iALK)))*1e-3
236 & * maskC(i,j,kLev,bi,bj)
237 surfphos(i,j) =
238 & max(1. _d -10,
239 & min(10. _d 0, Ptracer(i,j,1,bi,bj,iPO4)))*1e-3
240 & * maskC(i,j,kLev,bi,bj)
241 surfsi(i,j) =
242 & max(1. _d -8,
243 & min(500. _d 0, Ptracer(i,j,1,bi,bj,iSi)))*1e-3
244 & * maskC(i,j,kLev,bi,bj)
245 surfsalt(i,j) =
246 & max(4. _d 0, min(50. _d 0, salt(i,j,kLev,bi,bj)))
247 surftemp(i,j) =
248 & max(-4. _d 0, min(39. _d 0, theta(i,j,kLev,bi,bj)))
249 c
250 WIND(i,j,bi,bj) = 5. _d 0*maskC(i,j,1,bi,bj)
251 AtmosP(i,j,bi,bj) = 1. _d 0*maskC(i,j,1,bi,bj)
252 ENDDO
253 ENDDO
254
255 CALL CARBON_COEFFS(
256 I surftemp,surfsalt,
257 I bi,bj,iMin,iMax,jMin,jMax,myThid)
258
259 C====================================================================
260
261 IF ( .NOT.pH_isLoaded ) THEN
262 C set guess of pH for first step here
263
264 print*,'QQ: pCO2 approximation method'
265 c first approximation
266 C$TAF LOOP = parallel
267 DO j=jMin,jMax
268 C$TAF LOOP = parallel
269 DO i=iMin,iMax
270 IF ( maskC(i,j,kLev,bi,bj) .NE. 0. _d 0) THEN
271 C$TAF init dic_surf = static, 10
272 DO it=1,10
273 C$TAF STORE pH(i,j,bi,bj), PTR_CO2(i,j,kLev) = dic_surf
274 C$TAF STORE surfalk(i,j), surfphos(i,j), surfsi(i,j) = dic_surf
275 CALL CALC_PCO2_APPROX(
276 I surftemp(i,j),surfsalt(i,j),
277 I surfdic(i,j), surfphos(i,j),
278 I surfsi(i,j),surfalk(i,j),
279 I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
280 I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
281 I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
282 I aksi(i,j,bi,bj),akf(i,j,bi,bj),
283 I ak0(i,j,bi,bj), fugf(i,j,bi,bj),
284 I ff(i,j,bi,bj),
285 I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
286 U pH(i,j,bi,bj),pCO2(i,j,bi,bj),CO3(i,j,bi,bj),
287 I myThid )
288 ENDDO
289 ENDIF
290 ENDDO
291 ENDDO
292 iprt = MIN(20,sNx)
293 jprt = MIN(20,sNy)
294 print*,'QQ first guess pH', pH(iprt,jprt,bi,bj),
295 & theta(iprt,jprt,1,bi,bj), salt(iprt,jprt,1,bi,bj),
296 & surfdic(iprt,jprt), surfphos(iprt,jprt),
297 & surfsi(iprt,jprt),surfalk(iprt,jprt)
298
299 ENDIF
300
301 C end bi,bj loops
302 ENDDO
303 ENDDO
304
305 RETURN
306 END
307 #endif /*ALLOW_CARBON*/
308
309 #endif /*DARWIN*/
310 #endif /*ALLOW_PTRACERS*/
311 c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22