/[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.16 - (hide annotations) (download)
Sun Apr 11 21:04:39 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint65b, checkpoint65a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.15: +1 -8 lines
remove few commented lines (left from previous check-in)

1 jmc 1.16 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_atmos.F,v 1.15 2010/04/11 20:59:27 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 jmc 1.15 C 3=interact with atmospheric box (use dic_pCO2 as initial atmos. value)
20    
21 stephd 1.1 C !USES: ===============================================================
22     IMPLICIT NONE
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "GRID.h"
27 dfer 1.8 #include "DIC_VARS.h"
28 stephd 1.1 #include "PTRACERS_SIZE.h"
29 jmc 1.15 #include "PTRACERS_PARAMS.h"
30 stephd 1.1 #include "PTRACERS_FIELDS.h"
31     #include "DIC_ATMOS.h"
32    
33     C !INPUT PARAMETERS: ===================================================
34 jmc 1.15 C istate :: 0=initial call, 1=subsequent calls
35 stephd 1.1 C myTime :: current time
36 jmc 1.15 C myIter :: current iteration number
37     C myThid :: my Thread Id number
38     INTEGER istate
39 stephd 1.1 _RL myTime
40 jmc 1.15 INTEGER myIter, myThid
41 stephd 1.1
42 jmc 1.15 #ifdef ALLOW_DIC
43    
44     #ifdef USE_ATMOSCO2
45     C if coupled to atmsopheric model, use the
46     C CO2 value passed from the coupler
47    
48     #else /* USE_ATMOSCO2 */
49    
50     C !FUNCTIONS: ====================================================
51 stephd 1.1 LOGICAL DIFFERENT_MULTIPLE
52     EXTERNAL DIFFERENT_MULTIPLE
53    
54     C !LOCAL VARIABLES: ====================================================
55 jmc 1.15 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
59    
60     _RL tile_flux (nSx,nSy)
61     _RL tile_carbon(nSx,nSy)
62     _RL total_flux
63     _RL total_carbon
64    
65     C for carbon budget ouput
66     INTEGER ioUnit
67     _RL total_ocean_carbon_old
68     _RL total_atmos_carbon_old
69     _RL total_carbon_old, carbon_diff
70     _RL year_diff_ocean, year_diff_atmos, year_total
71     _RL start_diff_ocean, start_diff_atmos, start_total
72 stephd 1.1 C variables for reading CO2 input files
73 jmc 1.15 _RL tmp
74 stephd 1.1 _RL aWght, bWght
75 jmc 1.15
76     LOGICAL timeCO2budget
77 stephd 1.1 CEOP
78    
79 jmc 1.15 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
80 stephd 1.1
81 jmc 1.15 ioUnit = standardMessageUnit
82 stephd 1.1
83 jmc 1.15 C user specified value (or default = 278 ppm)- set only once
84     IF ( (dic_int1.EQ.0 .OR. dic_int1.EQ.1) .AND. istate.EQ.0 ) THEN
85     DO bj=myByLo(myThid),myByHi(myThid)
86     DO bi=myBxLo(myThid),myBxHi(myThid)
87     DO j=1-OLy,sNy+OLy
88     DO i=1-OLx,sNx+OLx
89 dfer 1.10 AtmospCO2(i,j,bi,bj)=dic_pCO2
90 jmc 1.15 ENDDO
91 stephd 1.1 ENDDO
92     ENDDO
93     ENDDO
94 jmc 1.15 ENDIF
95 stephd 1.1
96 jmc 1.15 C read from a file (note:
97     C dic_int2=number entries to read
98     C dic_int3=start timestep,
99     C dic_int4=timestep between file entries)
100     IF (dic_int1.EQ.2) THEN
101     C linearly interpolate between file entries
102     ntim=int((myIter-dic_int3)/dic_int4)+1
103     aWght = FLOAT(myIter-dic_int3)
104     bWght = FLOAT(dic_int4)
105     aWght = 0.5 _d 0 + aWght/bWght - FLOAT(ntim-1)
106     IF (aWght.GT.1. _d 0) THEN
107     ntim=ntim+1
108     aWght=aWght-1. _d 0
109     ENDIF
110     bWght = 1. _d 0 - aWght
111     tmp=co2atmos(ntim)*bWght+co2atmos(ntim+1)*aWght
112     WRITE(ioUnit,*) 'weights',ntim, aWght, bWght, tmp
113    
114     DO bj=myByLo(myThid),myByHi(myThid)
115     DO bi=myBxLo(myThid),myBxHi(myThid)
116     DO j=1-OLy,sNy+OLy
117 stephd 1.1 DO i=1-OLx,sNx+OLx
118     AtmospCO2(i,j,bi,bj)=tmp
119     ENDDO
120     ENDDO
121 jmc 1.15 ENDDO
122     ENDDO
123 stephd 1.1
124 jmc 1.15 ENDIF
125 stephd 1.1
126 jmc 1.15 C interactive atmosphere
127     IF (dic_int1.EQ.3) THEN
128 stephd 1.1
129 jmc 1.15 C Mass dry atmosphere = (5.1352+/-0.0003)d18 kg (Trenberth & Smith,
130     C Journal of Climate 2005)
131     C and Mean molecular mass air = 28.97 g/mol (NASA earth fact sheet)
132 stephd 1.3 total_atmos_moles= 1.77 _d 20
133 jmc 1.15 C for 278ppmv we need total_atmos_carbon=4.9206e+16
134 stephd 1.1
135     DO bj=myByLo(myThid),myByHi(myThid)
136     DO bi=myBxLo(myThid),myBxHi(myThid)
137 jmc 1.15 tile_flux(bi,bj) = 0.
138     tile_carbon(bi,bj) = 0.
139     IF (istate.GT.0) THEN
140     DO j=1,sNy
141     DO i=1,sNx
142     tile_flux(bi,bj) = tile_flux(bi,bj)
143     & + FluxCO2(i,j,bi,bj)*rA(i,j,bi,bj)
144     & *maskC(i,j,1,bi,bj)*dTtracerLev(1)
145     ENDDO
146     ENDDO
147     ENDIF
148     DO k=1,Nr
149 stephd 1.1 DO j=1,sNy
150 jmc 1.15 DO i=1,sNx
151     tile_carbon(bi,bj) = tile_carbon(bi,bj)
152     & + ( pTracer(i,j,k,bi,bj,1)
153 dfer 1.7 #ifdef DIC_BIOTIC
154 jmc 1.15 & +R_cp*pTracer(i,j,k,bi,bj,4)
155 dfer 1.7 #endif
156 jmc 1.15 & ) * rA(i,j,bi,bj)
157     & *drF(k)*hFacC(i,j,k,bi,bj)
158     ENDDO
159 stephd 1.1 ENDDO
160     ENDDO
161     ENDDO
162     ENDDO
163 stephd 1.2
164 jmc 1.15 CALL GLOBAL_SUM_TILE_RL( tile_flux, total_flux, myThid )
165     CALL GLOBAL_SUM_TILE_RL( tile_carbon, total_carbon, myThid )
166 stephd 1.1
167 jmc 1.15 IF (istate.EQ.0) THEN
168     C use dic_pCO2 as initial atmospheric pCO2 (not restart case):
169     _BEGIN_MASTER(myThid)
170     atpco2 = dic_pCO2
171     total_atmos_carbon = total_atmos_moles*dic_pCO2
172     _END_MASTER(myThid)
173     IF ( nIter0.GT.PTRACERS_Iter0 .OR.
174     & (nIter0.EQ.PTRACERS_Iter0 .AND. pickupSuff.NE.' ')
175     & ) THEN
176     C restart case: read previous atmospheric CO2 content & pCO2 from pickup file
177     CALL DIC_READ_CO2_PICKUP( nIter0, myThid )
178     ENDIF
179     _BEGIN_MASTER(myThid)
180     C store initial content:
181     total_ocean_carbon_start=total_carbon
182     total_atmos_carbon_start=total_atmos_carbon
183     total_ocean_carbon_old = total_carbon
184     total_atmos_carbon_old = total_atmos_carbon
185     _END_MASTER(myThid)
186     ELSE
187     _BEGIN_MASTER(myThid)
188     #ifdef ALLOW_AUTODIFF_TAMC
189     atpco2 = dic_pCO2
190 stephd 1.14 #endif
191 jmc 1.15 C store previous content:
192     total_ocean_carbon_old = total_ocean_carbon
193     total_atmos_carbon_old = total_atmos_carbon
194     C calculate new atmos pCO2
195     total_atmos_carbon = total_atmos_carbon - total_flux
196     _END_MASTER(myThid)
197 stephd 1.14 ENDIF
198 jmc 1.15 _BEGIN_MASTER(myThid)
199     total_ocean_carbon = total_carbon
200     atpco2 = total_atmos_carbon/total_atmos_moles
201 stephd 1.14
202 jmc 1.15 WRITE(ioUnit,*) 'QQ atmos C, total, pCo2',
203     & total_atmos_carbon, atpco2
204     total_carbon=total_atmos_carbon + total_ocean_carbon
205     total_carbon_old=total_atmos_carbon_old + total_ocean_carbon_old
206     carbon_diff=total_carbon-total_carbon_old
207     WRITE(ioUnit,*) 'QQ total C, current, old, diff',
208     & total_carbon, total_carbon_old, carbon_diff
209     carbon_diff=total_ocean_carbon-total_ocean_carbon_old
210     WRITE(ioUnit,*) 'QQ ocean C, current, old, diff',
211     & total_ocean_carbon, total_ocean_carbon_old, carbon_diff
212     WRITE(ioUnit,*) 'QQ air-sea flux, addition diff',
213     & total_flux, carbon_diff-total_flux
214    
215     C if end of forcing cycle, find total change in ocean carbon
216     IF (istate.EQ.0) THEN
217     total_ocean_carbon_year = total_ocean_carbon
218     total_atmos_carbon_year = total_atmos_carbon
219     ELSE
220     timeCO2budget =
221     & DIFFERENT_MULTIPLE(externForcingCycle,myTime,deltaTClock)
222     IF ( timeCO2budget ) THEN
223     year_diff_ocean = total_ocean_carbon-total_ocean_carbon_year
224     year_diff_atmos = total_atmos_carbon-total_atmos_carbon_year
225     year_total = (total_ocean_carbon+total_atmos_carbon) -
226     & (total_ocean_carbon_year+total_atmos_carbon_year)
227     start_diff_ocean = total_ocean_carbon-total_ocean_carbon_start
228     start_diff_atmos = total_atmos_carbon-total_atmos_carbon_start
229     start_total = (total_ocean_carbon+total_atmos_carbon) -
230     & (total_ocean_carbon_start+total_atmos_carbon_start)
231     WRITE(ioUnit,*) 'QQ YEAR END'
232     WRITE(ioUnit,*) 'year diff: ocean, atmos, total',
233     & year_diff_ocean, year_diff_atmos, year_total
234     WRITE(ioUnit,*) 'start diff: ocean, atmos, total ',
235     & start_diff_ocean, start_diff_atmos, start_total
236    
237     total_ocean_carbon_year = total_ocean_carbon
238     total_atmos_carbon_year = total_atmos_carbon
239     ENDIF
240     ENDIF
241 stephd 1.1
242 jmc 1.15 _END_MASTER(myThid)
243     _BARRIER
244 stephd 1.1
245 jmc 1.15 C-- Set AtmospCO2 for next iteration:
246 stephd 1.1 DO bj=myByLo(myThid),myByHi(myThid)
247     DO bi=myBxLo(myThid),myBxHi(myThid)
248     DO j=1-OLy,sNy+OLy
249     DO i=1-OLx,sNx+OLx
250 jmc 1.15 AtmospCO2(i,j,bi,bj) = atpco2
251 stephd 1.1 ENDDO
252     ENDDO
253     ENDDO
254 dfer 1.12 ENDDO
255 stephd 1.1
256 jmc 1.15 ENDIF
257 stephd 1.1
258 jmc 1.15 #endif /* ndef USE_ATMOSCO2 */
259 stephd 1.1
260 jmc 1.15 #endif /* ALLOW_DIC */
261 stephd 1.1
262 jmc 1.6 RETURN
263     END

  ViewVC Help
Powered by ViewVC 1.1.22