/[MITgcm]/MITgcm_contrib/darwin2/pkg/darwin/dic_atmos.F
ViewVC logotype

Contents of /MITgcm_contrib/darwin2/pkg/darwin/dic_atmos.F

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


Revision 1.2 - (show annotations) (download)
Mon May 9 20:17:39 2011 UTC (14 years, 3 months ago) by stephd
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt62x_20110513
Changes since 1.1: +11 -0 lines
o add extra bounds to dic/temp/salt so pH solver doesn't blow up

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 j=1-OLy,sNy+OLy
86 DO i=1-OLx,sNx+OLx
87 AtmospCO2(i,j,bi,bj)=apco2(i,j,bi,bj)
88 ENDDO
89 ENDDO
90 #else
91
92 c default - set only once
93 if (dic_int1.eq.0.and.istate.eq.0) then
94 DO bj=myByLo(myThid),myByHi(myThid)
95 DO bi=myBxLo(myThid),myBxHi(myThid)
96
97 DO j=1-OLy,sNy+OLy
98 DO i=1-OLx,sNx+OLx
99 AtmospCO2(i,j,bi,bj)=278.0 _d -6
100 ENDDO
101 ENDDO
102
103 ENDDO
104 ENDDO
105 endif
106
107 c user specified value - set only once
108 if (dic_int1.eq.1.and.istate.eq.0) then
109 DO bj=myByLo(myThid),myByHi(myThid)
110 DO bi=myBxLo(myThid),myBxHi(myThid)
111
112 DO j=1-OLy,sNy+OLy
113 DO i=1-OLx,sNx+OLx
114 AtmospCO2(i,j,bi,bj)=dic_pCO2
115 ENDDO
116 ENDDO
117
118 ENDDO
119 ENDDO
120 endif
121
122 c read from a file (note:
123 c dic_int2=number entries to read
124 c dic_int3=start timestep,
125 c dic_int4=timestep between file entries)
126 if (dic_int1.eq.2) then
127 c linearly interpolate between file entries
128 ntim=int((myIter-dic_int3)/dic_int4)+1
129 aWght = FLOAT(myIter-dic_int3)
130 bWght = FLOAT(dic_int4)
131 aWght = 0.5 _d 0 + aWght/bWght - FLOAT(ntim-1)
132 if (aWght.gt.1. _d 0) then
133 ntim=ntim+1
134 aWght=aWght-1. _d 0
135 endif
136 bWght = 1. _d 0 - aWght
137 tmp=co2atmos(ntim)*bWght+co2atmos(ntim+1)*aWght
138 c print*,'weights',ntim, aWght, bWght, tmp
139
140 DO bj=myByLo(myThid),myByHi(myThid)
141 DO bi=myBxLo(myThid),myBxHi(myThid)
142
143 DO j=1-OLy,sNy+OLy
144 DO i=1-OLx,sNx+OLx
145 AtmospCO2(i,j,bi,bj)=tmp
146 ENDDO
147 ENDDO
148
149 c print*,'AtmospCO2(20,20)',AtmospCO2(20,20,bi,bj)
150
151 ENDDO
152 ENDDO
153
154
155 endif
156
157
158 c interactive atmosphere
159 if (dic_int1.eq.3) then
160
161 c _BEGIN_MASTER(myThid)
162
163 cMass dry atmosphere = (5.1352+/-0.0003)d18 kg (Trenberth & Smith,
164 cJournal of Climate 2005)
165 cand Mean molecular mass air = 28.97 g/mol (NASA earth fact sheet)
166 total_atmos_moles= 1.77 _d 20
167 c for 278ppmv we need total_atmos_carbon=4.9206e+16
168
169 if (istate.gt.0) then
170 total_ocean_carbon_old=total_ocean_carbon
171 total_atmos_carbon_old=total_atmos_carbon
172 else
173 total_ocean_carbon_old=0. _d 0
174 total_atmos_carbon_old=0. _d 0
175 endif
176
177 total_flux= 0. _d 0
178 total_ocean_carbon= 0. _d 0
179
180 DO bj=myByLo(myThid),myByHi(myThid)
181 DO bi=myBxLo(myThid),myBxHi(myThid)
182 DO i=1,sNx
183 DO j=1,sNy
184 if (istate.gt.0) then
185 total_flux=total_flux+FluxCO2(i,j,bi,bj)*rA(i,j,bi,bj)*
186 & maskC(i,j,1,bi,bj)*dTtracerLev(1)
187 endif
188 DO k=1,nR
189 c QQQQQ NOT SET UP FOR DARWIN YET QQQQQQQQQQQQ
190 c total_ocean_carbon= total_ocean_carbon+
191 c & ( Ptracer(i,j,k,bi,bj,iDIC)
192 c & +R_cp*Ptracer(i,j,k,bi,bj,iPO4)
193 c & ) * rA(i,j,bi,bj)*
194 c & drF(k)*hFacC(i,j,k,bi,bj)
195 ENDDO
196 ENDDO
197 ENDDO
198 ENDDO
199 ENDDO
200
201 _GLOBAL_SUM_RL(total_flux,myThid)
202 _GLOBAL_SUM_RL(total_ocean_carbon,myThid)
203
204 if (istate.eq.0) then
205 c use value read in dic_init_fixed
206 total_atmos_carbon=total_atmos_carbon_ini
207 else
208 c calculate new atmos pCO2
209 total_atmos_carbon=total_atmos_carbon - total_flux
210 c write out if time for a new pickup
211 permCheckPoint = .FALSE.
212 permCheckPoint =
213 & DIFFERENT_MULTIPLE(pChkptFreq,myTime,deltaTClock)
214 if (permCheckPoint) then
215 DO i = 1,MAX_LEN_FNAM
216 fn(i:i) = ' '
217 ENDDO
218 WRITE(fn,'(A,I10.10)') 'dic_atmos.',myIter
219 C Going to really do some IO. Make everyone except master thread wait.
220 _BARRIER
221 c write values to new pickup
222
223 CALL MDSFINDUNIT( iUnit, myThid )
224 open(iUnit,file=fn,status='new')
225 write(iUnit,*) total_atmos_carbon, atpco2
226 close(iUnit)
227
228 endif
229 endif
230
231 atpco2=total_atmos_carbon/total_atmos_moles
232
233 c print*,'QQpCO2', total_atmos_carbon, atpco2, total_ocean_carbon,
234 c & total_flux
235
236 DO bj=myByLo(myThid),myByHi(myThid)
237 DO bi=myBxLo(myThid),myBxHi(myThid)
238
239 DO j=1-OLy,sNy+OLy
240 DO i=1-OLx,sNx+OLx
241 AtmospCO2(i,j,bi,bj)=atpco2
242 ENDDO
243 ENDDO
244
245 ENDDO
246 ENDDO
247
248 print*,'QQ atmos C, total, pCo2', total_atmos_carbon, atpco2
249 total_carbon=total_atmos_carbon + total_ocean_carbon
250 total_carbon_old=total_atmos_carbon_old + total_ocean_carbon_old
251 carbon_diff=total_carbon-total_carbon_old
252 print*,'QQ total C, current, old, diff', total_carbon,
253 & total_carbon_old, carbon_diff
254 carbon_diff=total_ocean_carbon-total_ocean_carbon_old
255 tmp=carbon_diff-total_flux
256 print*,'QQ ocean C, current, old, diff',total_ocean_carbon,
257 & total_ocean_carbon_old, carbon_diff
258 print*,'QQ air-sea flux, addition diff', total_flux, tmp
259
260 c if end of forcing cycle, find total change in ocean carbon
261 if (istate.eq.0) then
262 total_ocean_carbon_start=total_ocean_carbon
263 total_ocean_carbon_year=total_ocean_carbon
264 total_atmos_carbon_start=total_atmos_carbon
265 total_atmos_carbon_year=total_atmos_carbon
266 else
267 permCheckPoint = .FALSE.
268 permCheckPoint =
269 & DIFFERENT_MULTIPLE(externForcingCycle,myTime,deltaTClock)
270 if (permCheckPoint) then
271 year_diff_ocean=total_ocean_carbon-total_ocean_carbon_year
272 year_diff_atmos=total_atmos_carbon-total_atmos_carbon_year
273 year_total=(total_ocean_carbon+total_atmos_carbon) -
274 & (total_ocean_carbon_year+total_atmos_carbon_year)
275 start_diff_ocean=total_ocean_carbon-total_ocean_carbon_start
276 start_diff_atmos=total_atmos_carbon-total_atmos_carbon_start
277 start_total=(total_ocean_carbon+total_atmos_carbon) -
278 & (total_ocean_carbon_start+total_atmos_carbon_start)
279 print*,'QQ YEAR END'
280 print*,'year diff: ocean, atmos, total', year_diff_ocean,
281 & year_diff_atmos, year_total
282 print*,'start diff: ocean, atmos, total ', start_diff_ocean,
283 & start_diff_atmos, start_total
284 c
285 total_ocean_carbon_year=total_ocean_carbon
286 total_atmos_carbon_year=total_atmos_carbon
287 endif
288 endif
289
290 c _END_MASTER(myThid)
291
292 endif
293
294 #endif
295 #endif
296
297 RETURN
298 END
299 #endif /*ALLOW_CARBON*/
300
301 #endif /*DARWIN*/
302 #endif /*ALLOW_PTRACERS*/
303 c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22