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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 13 18:56:24 2011 UTC (14 years, 3 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_baseline
darwin2 initial checkin

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

  ViewVC Help
Powered by ViewVC 1.1.22