/[MITgcm]/MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/dic_atmos.F
ViewVC logotype

Contents of /MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/dic_atmos.F

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


Revision 1.1 - (show annotations) (download)
Tue Nov 28 19:50:42 2017 UTC (7 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Holger Brix's ECCO-Darwin version 3 with circa-2011 MITgcm

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

  ViewVC Help
Powered by ViewVC 1.1.22