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_ATMOS |
12 |
|
13 |
C !INTERFACE: ========================================================== |
14 |
SUBROUTINE DIC_ATMOS( istate, myTime, myIter, myThid ) |
15 |
|
16 |
C !DESCRIPTION: |
17 |
C Calculate the atmospheric pCO2 |
18 |
C dic_int1: |
19 |
C 0=use default 278.d-6 |
20 |
C 1=use constant value - dic_pCO2, read in from data.dic |
21 |
C 2=read in from file |
22 |
C 3=interact with atmospheric box |
23 |
C !USES: =============================================================== |
24 |
IMPLICIT NONE |
25 |
#include "SIZE.h" |
26 |
#include "DYNVARS.h" |
27 |
#include "EEPARAMS.h" |
28 |
#include "PARAMS.h" |
29 |
#include "GRID.h" |
30 |
#include "FFIELDS.h" |
31 |
#include "DARWIN_SIZE.h" |
32 |
#include "DARWIN_IO.h" |
33 |
#include "DARWIN_FLUX.h" |
34 |
#include "PTRACERS_SIZE.h" |
35 |
#include "PTRACERS_FIELDS.h" |
36 |
#include "DIC_ATMOS.h" |
37 |
#ifdef USE_EXFWIND |
38 |
#include "EXF_FIELDS.h" |
39 |
#endif |
40 |
|
41 |
C !INPUT PARAMETERS: =================================================== |
42 |
C myThid :: thread number |
43 |
C myIter :: current timestep |
44 |
C myTime :: current time |
45 |
C istate :: 0=initial call, 1=subsequent calls |
46 |
INTEGER myIter, myThid, istate |
47 |
_RL myTime |
48 |
|
49 |
LOGICAL DIFFERENT_MULTIPLE |
50 |
EXTERNAL DIFFERENT_MULTIPLE |
51 |
|
52 |
C !LOCAL VARIABLES: ==================================================== |
53 |
INTEGER bi, bj, I,J,k |
54 |
INTEGER ntim, iUnit |
55 |
c |
56 |
_RL total_flux |
57 |
_RL total_ocean_carbon_old |
58 |
_RL total_atmos_carbon_old |
59 |
_RL total_atmos_moles |
60 |
_RL atpco2 |
61 |
_RL total_carbon_old, total_carbon, carbon_diff |
62 |
_RL tmp |
63 |
_RL year_diff_ocean, year_diff_atmos, year_total |
64 |
_RL start_diff_ocean, start_diff_atmos, start_total |
65 |
C variables for reading CO2 input files |
66 |
_RL aWght, bWght |
67 |
c |
68 |
CHARACTER*(MAX_LEN_FNAM) fn |
69 |
LOGICAL permCheckPoint |
70 |
CEOP |
71 |
|
72 |
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc |
73 |
|
74 |
c if coupled to atmsopheric model, use the |
75 |
c Co2 value passed from the coupler |
76 |
#ifndef USE_ATMOSCO2 |
77 |
|
78 |
IF ( nThreads .GT. 1 .AND. |
79 |
& ( dic_int1.EQ.2 .OR. dic_int1.EQ.3 ) ) THEN |
80 |
C Problem with I/O and global-sum for multi-threaded execution |
81 |
C Needs to be fixed before using this S/R in multi-threaded run |
82 |
STOP 'S/R DIC_ATMOS: multi-threaded not right' |
83 |
ENDIF |
84 |
# ifdef USE_EXFCO2 |
85 |
DO bj=myByLo(myThid),myByHi(myThid) |
86 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
87 |
DO j=1-OLy,sNy+OLy |
88 |
DO i=1-OLx,sNx+OLx |
89 |
AtmospCO2(i,j,bi,bj)=apco2(i,j,bi,bj) |
90 |
ENDDO |
91 |
ENDDO |
92 |
ENDDO |
93 |
ENDDO |
94 |
# else |
95 |
|
96 |
c default - set only once |
97 |
if (dic_int1.eq.0.and.istate.eq.0) then |
98 |
DO bj=myByLo(myThid),myByHi(myThid) |
99 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
100 |
|
101 |
DO j=1-OLy,sNy+OLy |
102 |
DO i=1-OLx,sNx+OLx |
103 |
AtmospCO2(i,j,bi,bj)=278.0 _d -6 |
104 |
ENDDO |
105 |
ENDDO |
106 |
|
107 |
ENDDO |
108 |
ENDDO |
109 |
endif |
110 |
|
111 |
c user specified value - set only once |
112 |
if (dic_int1.eq.1.and.istate.eq.0) then |
113 |
DO bj=myByLo(myThid),myByHi(myThid) |
114 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
115 |
|
116 |
DO j=1-OLy,sNy+OLy |
117 |
DO i=1-OLx,sNx+OLx |
118 |
AtmospCO2(i,j,bi,bj)=dic_pCO2 |
119 |
ENDDO |
120 |
ENDDO |
121 |
|
122 |
ENDDO |
123 |
ENDDO |
124 |
endif |
125 |
|
126 |
c read from a file (note: |
127 |
c dic_int2=number entries to read |
128 |
c dic_int3=start timestep, |
129 |
c dic_int4=timestep between file entries) |
130 |
if (dic_int1.eq.2) then |
131 |
c linearly interpolate between file entries |
132 |
ntim=int((myIter-dic_int3)/dic_int4)+1 |
133 |
aWght = FLOAT(myIter-dic_int3) |
134 |
bWght = FLOAT(dic_int4) |
135 |
aWght = 0.5 _d 0 + aWght/bWght - FLOAT(ntim-1) |
136 |
if (aWght.gt.1. _d 0) then |
137 |
ntim=ntim+1 |
138 |
aWght=aWght-1. _d 0 |
139 |
endif |
140 |
bWght = 1. _d 0 - aWght |
141 |
tmp=co2atmos(ntim)*bWght+co2atmos(ntim+1)*aWght |
142 |
c print*,'weights',ntim, aWght, bWght, tmp |
143 |
|
144 |
DO bj=myByLo(myThid),myByHi(myThid) |
145 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
146 |
|
147 |
DO j=1-OLy,sNy+OLy |
148 |
DO i=1-OLx,sNx+OLx |
149 |
AtmospCO2(i,j,bi,bj)=tmp |
150 |
ENDDO |
151 |
ENDDO |
152 |
|
153 |
c print*,'AtmospCO2(20,20)',AtmospCO2(20,20,bi,bj) |
154 |
|
155 |
ENDDO |
156 |
ENDDO |
157 |
|
158 |
|
159 |
endif |
160 |
|
161 |
|
162 |
c interactive atmosphere |
163 |
if (dic_int1.eq.3) then |
164 |
|
165 |
c _BEGIN_MASTER(myThid) |
166 |
|
167 |
cMass dry atmosphere = (5.1352+/-0.0003)d18 kg (Trenberth & Smith, |
168 |
cJournal of Climate 2005) |
169 |
cand Mean molecular mass air = 28.97 g/mol (NASA earth fact sheet) |
170 |
total_atmos_moles= 1.77 _d 20 |
171 |
c for 278ppmv we need total_atmos_carbon=4.9206e+16 |
172 |
|
173 |
if (istate.gt.0) then |
174 |
total_ocean_carbon_old=total_ocean_carbon |
175 |
total_atmos_carbon_old=total_atmos_carbon |
176 |
else |
177 |
total_ocean_carbon_old=0. _d 0 |
178 |
total_atmos_carbon_old=0. _d 0 |
179 |
endif |
180 |
|
181 |
total_flux= 0. _d 0 |
182 |
total_ocean_carbon= 0. _d 0 |
183 |
|
184 |
DO bj=myByLo(myThid),myByHi(myThid) |
185 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
186 |
DO i=1,sNx |
187 |
DO j=1,sNy |
188 |
if (istate.gt.0) then |
189 |
total_flux=total_flux+FluxCO2(i,j,bi,bj)*rA(i,j,bi,bj)* |
190 |
& maskC(i,j,1,bi,bj)*dTtracerLev(1) |
191 |
endif |
192 |
DO k=1,nR |
193 |
c QQQQQ NOT SET UP FOR DARWIN YET QQQQQQQQQQQQ |
194 |
c total_ocean_carbon= total_ocean_carbon+ |
195 |
c & ( Ptracer(i,j,k,bi,bj,iDIC) |
196 |
c & +R_cp*Ptracer(i,j,k,bi,bj,iPO4) |
197 |
c & ) * rA(i,j,bi,bj)* |
198 |
c & drF(k)*hFacC(i,j,k,bi,bj) |
199 |
ENDDO |
200 |
ENDDO |
201 |
ENDDO |
202 |
ENDDO |
203 |
ENDDO |
204 |
|
205 |
_GLOBAL_SUM_RL(total_flux,myThid) |
206 |
_GLOBAL_SUM_RL(total_ocean_carbon,myThid) |
207 |
|
208 |
if (istate.eq.0) then |
209 |
c use value read in dic_init_fixed |
210 |
total_atmos_carbon=total_atmos_carbon_ini |
211 |
else |
212 |
c calculate new atmos pCO2 |
213 |
total_atmos_carbon=total_atmos_carbon - total_flux |
214 |
c write out if time for a new pickup |
215 |
permCheckPoint = .FALSE. |
216 |
permCheckPoint = |
217 |
& DIFFERENT_MULTIPLE(pChkptFreq,myTime,deltaTClock) |
218 |
if (permCheckPoint) then |
219 |
DO i = 1,MAX_LEN_FNAM |
220 |
fn(i:i) = ' ' |
221 |
ENDDO |
222 |
WRITE(fn,'(A,I10.10)') 'dic_atmos.',myIter |
223 |
C Going to really do some IO. Make everyone except master thread wait. |
224 |
_BARRIER |
225 |
c write values to new pickup |
226 |
|
227 |
CALL MDSFINDUNIT( iUnit, myThid ) |
228 |
open(iUnit,file=fn,status='new') |
229 |
write(iUnit,*) total_atmos_carbon, atpco2 |
230 |
close(iUnit) |
231 |
|
232 |
endif |
233 |
endif |
234 |
|
235 |
atpco2=total_atmos_carbon/total_atmos_moles |
236 |
|
237 |
c print*,'QQpCO2', total_atmos_carbon, atpco2, total_ocean_carbon, |
238 |
c & total_flux |
239 |
|
240 |
DO bj=myByLo(myThid),myByHi(myThid) |
241 |
DO bi=myBxLo(myThid),myBxHi(myThid) |
242 |
|
243 |
DO j=1-OLy,sNy+OLy |
244 |
DO i=1-OLx,sNx+OLx |
245 |
AtmospCO2(i,j,bi,bj)=atpco2 |
246 |
ENDDO |
247 |
ENDDO |
248 |
|
249 |
ENDDO |
250 |
ENDDO |
251 |
|
252 |
print*,'QQ atmos C, total, pCo2', total_atmos_carbon, atpco2 |
253 |
total_carbon=total_atmos_carbon + total_ocean_carbon |
254 |
total_carbon_old=total_atmos_carbon_old + total_ocean_carbon_old |
255 |
carbon_diff=total_carbon-total_carbon_old |
256 |
print*,'QQ total C, current, old, diff', total_carbon, |
257 |
& total_carbon_old, carbon_diff |
258 |
carbon_diff=total_ocean_carbon-total_ocean_carbon_old |
259 |
tmp=carbon_diff-total_flux |
260 |
print*,'QQ ocean C, current, old, diff',total_ocean_carbon, |
261 |
& total_ocean_carbon_old, carbon_diff |
262 |
print*,'QQ air-sea flux, addition diff', total_flux, tmp |
263 |
|
264 |
c if end of forcing cycle, find total change in ocean carbon |
265 |
if (istate.eq.0) then |
266 |
total_ocean_carbon_start=total_ocean_carbon |
267 |
total_ocean_carbon_year=total_ocean_carbon |
268 |
total_atmos_carbon_start=total_atmos_carbon |
269 |
total_atmos_carbon_year=total_atmos_carbon |
270 |
else |
271 |
permCheckPoint = .FALSE. |
272 |
permCheckPoint = |
273 |
& DIFFERENT_MULTIPLE(externForcingCycle,myTime,deltaTClock) |
274 |
if (permCheckPoint) then |
275 |
year_diff_ocean=total_ocean_carbon-total_ocean_carbon_year |
276 |
year_diff_atmos=total_atmos_carbon-total_atmos_carbon_year |
277 |
year_total=(total_ocean_carbon+total_atmos_carbon) - |
278 |
& (total_ocean_carbon_year+total_atmos_carbon_year) |
279 |
start_diff_ocean=total_ocean_carbon-total_ocean_carbon_start |
280 |
start_diff_atmos=total_atmos_carbon-total_atmos_carbon_start |
281 |
start_total=(total_ocean_carbon+total_atmos_carbon) - |
282 |
& (total_ocean_carbon_start+total_atmos_carbon_start) |
283 |
print*,'QQ YEAR END' |
284 |
print*,'year diff: ocean, atmos, total', year_diff_ocean, |
285 |
& year_diff_atmos, year_total |
286 |
print*,'start diff: ocean, atmos, total ', start_diff_ocean, |
287 |
& start_diff_atmos, start_total |
288 |
c |
289 |
total_ocean_carbon_year=total_ocean_carbon |
290 |
total_atmos_carbon_year=total_atmos_carbon |
291 |
endif |
292 |
endif |
293 |
|
294 |
c _END_MASTER(myThid) |
295 |
|
296 |
endif |
297 |
|
298 |
# endif /*USE_EXFCO2*/ |
299 |
#endif |
300 |
|
301 |
RETURN |
302 |
END |
303 |
#endif /*ALLOW_CARBON*/ |
304 |
|
305 |
#endif /*DARWIN*/ |
306 |
#endif /*ALLOW_PTRACERS*/ |
307 |
c ================================================================== |