/[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.14 - (hide annotations) (download)
Thu Sep 10 21:09:57 2009 UTC (15 years, 10 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.13: +17 -1 lines
o for running MPI - only first processor writes dic_amos.*** file

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

  ViewVC Help
Powered by ViewVC 1.1.22