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

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

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


Revision 1.10 - (hide annotations) (download)
Tue Apr 8 20:21:35 2008 UTC (17 years, 3 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint59p
Changes since 1.9: +16 -17 lines
Moving forcing-related filenames and parameters from gchem to dic/cfc

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

  ViewVC Help
Powered by ViewVC 1.1.22