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

Contents of /MITgcm/pkg/dic/dic_atmos.F

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


Revision 1.7 - (show annotations) (download)
Fri Apr 4 18:57:36 2008 UTC (16 years, 2 months ago) by dfer
Branch: MAIN
Changes since 1.6: +8 -5 lines
Some fixes for the "#undef DIC_BI0TIC" case

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

  ViewVC Help
Powered by ViewVC 1.1.22