/[MITgcm]/MITgcm_contrib/jscott/igsm/src/trends4ipcc.F
ViewVC logotype

Annotation of /MITgcm_contrib/jscott/igsm/src/trends4ipcc.F

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


Revision 1.1 - (hide annotations) (download)
Fri Aug 11 19:35:33 2006 UTC (18 years, 11 months ago) by jscott
Branch: MAIN
atm2d package

1 jscott 1.1 #include "ctrparam.h"
2    
3     SUBROUTINE GTREND(XGAS,YEART,NGAS) 9155.9
4     C 9156.
5     C-----------------------------------------------------------------------9156.1
6     C T-GAS SCENARIO G: 9156.2
7     C 9156.3
8     C 9156.4
9     C CO2: 9156.5
10     C x.xx/YR INCREASE form YEART 9156.6
11     C 9156.7
12     C N2O, CH4 and CFC for YEART
13     C 9158.4
14     C-----------------------------------------------------------------------9158.5
15     C 9158.6
16     DIMENSION XGAS(5) 9158.7
17     COMMON/CO2TRND/ALFFOR,CO2TR,YEARGT,CO2IN,INYRAD
18     common/ BACKGRGHG/GHGBGR(5)
19     save
20     data ifirst /0/
21     C 9160.8
22     if (ifirst.eq.0)then
23     c if(ALFFOR.gt.0.0)then
24     CO2IN=GHGBGR(1)
25     c endif
26     print *,' gtrend.f',100*ALFFOR,'% per year from',CO2IN
27     print *,'N2O, CH4 and CFCs '
28     print '(4e10.2)',(GHGBGR(ii),ii=2,5)
29     c ifirst=1
30     endif
31     YEAR=YEART
32     DT=YEAR-INYRAD
33     XX0=CO2IN
34     XX=XX0*(1.+ALFFOR)**DT
35     XGAS(1)=XX 9182.3
36     CO2TR=XGAS(1)
37     do ii=2,5
38     XGAS(ii)=GHGBGR(ii)
39     enddo
40     if (ifirst.eq.0)then
41     print *,'From GTREND'
42     print '(5e12.4)',(XGAS(ii),ii=1,5)
43     ifirst=1
44     endif
45     RETURN 9182.5
46     END 9182.6
47     ! ----------------------------------------------------------
48    
49     subroutine bmtrnd(XGASS,YEAR,NGAS)
50     parameter (nyd=2000,nyd1=nyd+1)
51     C
52     C
53     C For simulations with observed forcing using equivalent
54     C CO2 concentrations from file co2_data
55     C Concentrations of other GHGs are
56     c those for 1958.
57     C DATA are annual means, but they are
58     C used as a data for the middle of the coresponding year
59     C
60     C
61     real XGASS(NGAS)
62     dimension XG1958(5), xf11(nyd),xf12(nyd),xco2(nyd),xn2o(nyd),
63     *xch4(nyd),ighgyr(nyd)
64     real xxf11(nyd1),xxf12(nyd1),xxco2(nyd1),xxn2o(nyd1),xxch4(nyd1)
65     common/boxmod/YEAR0
66     common /bmtrdata/co2_data
67     common/ BACKGRGHG/GHGBGR(5)
68     character * 120 co2_data
69     logical first
70     data first /.true./
71     data ncall /1/
72     if(first)then
73     print *,' BMTREND for observed forcing'
74     open (unit=561,file=co2_data,
75     * status='OLD',form='formatted')
76     do 50 i=1,nyd
77     c read (561,501,end=500),ighgyr(i),tmp,xco2(i)
78     read (561,*,end=500),ighgyr(i),xco2(i)
79     50 continue
80     500 continue
81     close (561)
82     do ii=1,5
83     XG1958(ii)=GHGBGR(ii)
84     enddo
85     ny=i-2
86     ny1=ny+1
87     ny2=ny+2
88     YEAR0=ighgyr(1)-1
89     print *,'From FORSET'
90     print *,' year=',year
91     print *,'YEAR0=',YEAR0
92     501 format(i4,2f8.2)
93     c xxco2(1)=XG1958(1)
94     xxco2(1)=2.*xco2(1)-xco2(2)
95     xxn2o(1)=XG1958(2)
96     xxch4(1)=XG1958(3)
97     xxf11(1)=XG1958(4)*1000.
98     xxf12(1)=XG1958(5)*1000.
99     do 10 i=1,ny1
100     xxco2(i+1)=xco2(i)
101     10 continue
102     first=.false.
103     endif
104     if(ncall.eq.2)then
105     print *,'BMTRND from FORGET'
106     print *,' year=',year
107     print *,'YEAR0=',YEAR0
108     endif
109     call ghgint(xx,xxco2,ny2,YEAR)
110     XGASS(1)=xx
111     XGASS(2)=XG1958(2)
112     XGASS(3)=XG1958(3)
113     XGASS(4)=XG1958(4)*1000.
114     XGASS(5)=XG1958(5)*1000.
115     if(ncall.lt.3)ncall=ncall+1
116     return
117     end
118    
119     subroutine ghgint(xx,xxf,ny,year)
120     common/boxmod/YEAR0
121     real xxf(ny)
122     i=year+0.5
123     dl=year+.5-i
124     i=i-YEAR0
125     if(i.lt.1.or.i.ge.ny)then
126     print *,' error in ghgint i=',i
127     stop 25
128     endif
129     xx=xxf(i)*(1.-dl)+xxf(i+1)*dl
130     return
131     end
132    
133     subroutine ghgint1(xx,xxf,iyear,ny,year)
134     common/boxmod/YEAR0
135     dimension xxf(ny),iyear(ny)
136     ! print *,ny,iyear(1),xxf(1)
137     do i=1,ny
138     year1=iyear(i)+0.5
139     year2=iyear(i+1)+0.5
140     c if(year.gt.iyear(i).and.year.le.iyear(i+1))go to 100
141     if(year.ge.year1.and.year.le.year2)go to 100
142     enddo
143     print *,' Wrong year year=',year
144     print *,'YEAR=',YEAR,year1,year2
145     stop
146     100 continue
147     c print *,'YEAR=',YEAR,year1,year2
148     c x=(iyear(i+1)-year)/(iyear(i+1)-iyear(i))
149     x=(year2-year)/(year2-year1)
150     xx=xxf(i+1)*(1.-x)+xxf(i)*x
151     c print *,i,x,xxf(i),xxf(i+1),xx
152     return
153     end
154     subroutine bmtrndmg(XGASS,YEAR,NGAS)
155     parameter (nyd=2000,nyd1=nyd+1)
156     c
157     c Multi-gas version of box-model trend routine
158     c - added 22 Aug 2002 - ceforest
159     C - greenhouse gas concentrations taken from GISS dataset on web
160     c - CFC-11 includes other long-lived gases
161     C
162     C DATA are annual means, but they are
163     C used as a data for the middle of the coresponding year
164     C
165     C
166     real XGASS(NGAS)
167     C version for SRES
168     dimension XG1958(5), xf11(nyd),xf12(nyd),xco2(nyd),xn2o(nyd),
169     *xch4(nyd),ighgyr(nyd),iyear(nyd1),xfothers(nyd)
170     real xxf11(nyd1),xxf12(nyd1),xxco2(nyd1),xxn2o(nyd1),xxch4(nyd1)
171     common/boxmod/YEAR0
172     common /bmtrdata/co2_data
173     common/ BACKGRGHG/GHGBGR(5)
174     character * 120 co2_data
175     logical first
176     data first /.true./
177     data ncall /1/
178     if(first)then
179     print *,' BMTRENDMG for observed forcing'
180     open (unit=561,file=co2_data,
181     * status='OLD',form='formatted')
182     do 50 i=1,nyd
183     c read (561,501,end=500),ighgyr(i),tmp,xco2(i)
184     c f11 includes other long-lived gases
185     read (561,*,end=500),ighgyr(i),xco2(i),xn2o(i),
186     * xch4(i), xf11(i),xf12(i),xfothers(i)
187     50 continue
188     500 continue
189     close (561)
190     do ii=1,5
191     XG1958(ii)=GHGBGR(ii)
192     enddo
193     ny=i-2
194     ny1=ny+1
195     ny2=ny+2
196     YEAR0=ighgyr(1)-1
197     iyear(1)=YEAR0
198     do i=1,ny1
199     iyear(i+1)=ighgyr(i)
200     enddo
201     print *,'From FORSET'
202     print *,' year=',year
203     print *,'YEAR0=',YEAR0
204     print *,'ny2=',ny2,' LYEAR=',iyear(ny2)
205     501 format(i4,2f8.2)
206     do i=1,ny
207     xf11(i)=xf11(i)+xfothers(i)
208     enddo
209     xxco2(1)=2.*xco2(1)-xco2(2)
210     xxn2o(1)=2.*xn2o(1)-xn2o(2)
211     xxch4(1)=2.*xch4(1)-xch4(2)
212     c xxf11(1)=(2.*xf11(1)-xf11(2))*1000.
213     c xxf12(1)=(2.*xf12(1)-xf12(2))*1000.
214     xxf11(1)=(2.*xf11(1)-xf11(2))
215     xxf12(1)=(2.*xf12(1)-xf12(2))
216     do 10 i=1,ny1
217     xxco2(i+1)=xco2(i)
218     xxn2o(i+1)=xn2o(i)
219     xxch4(i+1)=xch4(i)
220     c xxf11(i+1)=xf11(i)*1000.
221     c xxf12(i+1)=xf12(i)*1000.
222     xxf11(i+1)=xf11(i)
223     xxf12(i+1)=xf12(i)
224     10 continue
225     first=.false.
226     endif
227     if(ncall.eq.2)then
228     print *,'BMTRND from FORGET'
229     print *,' year=',year
230     print *,'YEAR0=',YEAR0
231     endif
232     call ghgint1(xx,xxco2,iyear,ny2,YEAR)
233     XGASS(1)=xx
234     call ghgint1(xx,xxn2o,iyear,ny2,YEAR)
235     XGASS(2)=xx
236     call ghgint1(xx,xxch4,iyear,ny2,YEAR)
237     XGASS(3)=xx
238     call ghgint1(xx,xxf11,iyear,ny2,YEAR)
239     XGASS(4)=xx
240     call ghgint1(xx,xxf12,iyear,ny2,YEAR)
241     XGASS(5)=xx
242     if(ncall.lt.3)ncall=ncall+1
243     return
244     end
245     ! ----------------------------------------------------------
246    
247     subroutine stbtrnd(XGASS,YEAR,NGAS,KTREN)
248     parameter (nyd=2000,nyd1=nyd+1)
249     C
250     C
251     C For IPCC stabilisation simulations
252     C CO2 concentrations from file co2_data
253     C Concentrations of other GHGs are
254     c those for 1765.
255     C DATA are annual means, but they are
256     C used as a data for the middle of the coresponding year
257     C
258     C
259     real XGASS(NGAS)
260     dimension XG1958(5), xf11(nyd),xf12(nyd),xco2(nyd),xn2o(nyd),
261     *xch4(nyd),ighgyr(nyd),iyear(nyd)
262     real xxf11(nyd1),xxf12(nyd1),xxco2(nyd1),xxn2o(nyd1),xxch4(nyd1)
263     real co2data(9)
264     common/boxmod/YEAR0
265     common /bmtrdata/co2_data
266     common/ BACKGRGHG/GHGBGR(5)
267     character * 120 co2_data
268     character * 10 name,scen(9)
269     logical first
270     data first /.true./
271     data ncall /1/
272     if(first)then
273     nsc=KTREN-KTREN/10*10
274     open (unit=561,file=co2_data,
275     * status='OLD',form='formatted')
276     read (561,*)name,scen
277     print *,' Simulation with scenario ',scen(nsc)
278     do 50 i=1,nyd
279     c read (561,501,end=500),ighgyr(i),tmp,xco2(i)
280     read (561,*,end=500),ighgyr(i),co2data
281     xco2(i)=co2data(nsc)
282     iyear(i+1)=ighgyr(i)
283     50 continue
284     500 continue
285     close (561)
286     do ii=1,5
287     XG1958(ii)=GHGBGR(ii)
288     enddo
289     ny=i-2
290     ny1=ny+1
291     ny2=ny+2
292     YEAR0=ighgyr(1)-1
293     iyear(1)=YEAR0
294     print *,'From FORSET STBTRND'
295     print *,' year=',year
296     print *,'YEAR0=',YEAR0
297     501 format(i4,2f8.2)
298     xxco2(1)=2.*xco2(1)-xco2(2)
299     xxn2o(1)=XG1958(2)
300     xxch4(1)=XG1958(3)
301     xxf11(1)=XG1958(4)*1000.
302     xxf12(1)=XG1958(5)*1000.
303     do 10 i=1,ny1
304     xxco2(i+1)=xco2(i)
305     10 continue
306     first=.false.
307     endif
308     ! call ghgint(xx,xxco2,ny2,YEAR)
309     call ghgint1(xx,xxco2,iyear,ny2,YEAR)
310     XGASS(1)=xx
311     XGASS(2)=XG1958(2)
312     XGASS(3)=XG1958(3)
313     XGASS(4)=XG1958(4)*1000.
314     XGASS(5)=XG1958(5)*1000.
315     if(ncall.eq.2)then
316     print *,'STBTRND from FORGET'
317     print *,' year=',year
318     print *,'YEAR0=',YEAR0
319     print *,'XGASS'
320     print *,XGASS
321     endif
322     if(ncall.lt.3)ncall=ncall+1
323     return
324     end
325    
326    
327     subroutine emissipcc(YEAR,tcu,ocu,xco2,xco2ann,nsc)
328     parameter (nyd=2000,nyd1=nyd+1)
329     C
330     C
331     C For IPCC stabilisation simulations with CO2 emissions
332     C CO2 emissions from file co2_data
333     C Concentrations of other GHGs are
334     c those for 1765.
335     C DATA are annual means, but they are
336     C used as a data for the middle of the coresponding year
337     C
338     C
339     !include "BD2G04.COM"
340     !include "TEM.COM"
341     !include "RADCOM.COM"
342     c common /Garyflux/pC_atm(jm0),wind_amp,fluxco2(jm0)
343     parameter(jm0=46)
344     common /ATCO2/atm_co2(jm0)
345     dimension xemi(nyd),eghgyr(nyd),xxemi(nyd1),iyear(nyd1)
346     real emidata(4),co2stocker(9),xxco2(nyd)
347     dimension NDAYMN(12)
348     data NDAYMN /31,28,31,30,31,30,31,31,30,31,30,31/
349    
350     common/boxmod/YEAR0
351     common /bmtrdata/co2_data
352     common /ipccdata/init_co2
353     common/ BACKGRGHG/GHGBGR(5)
354     character * 120 co2_data
355     character * 10 name,scen(4)
356     logical first
357     data first /.true./
358     data ncall /1/
359     if(first)then
360     open (unit=561,file=co2_data,
361     * status='OLD',form='formatted')
362     read (561,*)name
363     read (561,*)name,scen
364     print *,'IPCC name=',name,' nsc=',nsc
365     print *,scen
366     print *,' Simulation with emission scenario ',scen(nsc)
367     do 50 i=1,nyd
368     read (561,*,end=500),eghgyr(i),emidata
369     xemi(i)=emidata(nsc)
370     c print *,eghgyr(i),xemi(i)
371     50 continue
372     500 continue
373     close (561)
374     ny=i-2
375     ny1=ny+1
376     ny2=ny+2
377     YEAR0=eghgyr(1)-1
378     print *,'From FORSET EMISSIPCC'
379     print *,' year=',year
380     print *,'YEAR0=',YEAR0
381     501 format(i4,2f8.2)
382     xxemi(1)=0.0
383     iyear(1)=YEAR0
384     do 10 i=1,ny1
385     iyear(i+1)=eghgyr(i)
386     xxemi(i+1)=xemi(i)
387     10 continue
388     dtemi=1./12.
389     first=.false.
390     endif
391    
392     c if(YEAR.lt.2101) then
393     c call ghgint(xx,xxemi,ny2,YEAR)
394     call ghgint1(xx,xxemi,iyear,ny2,YEAR)
395     c else
396     c xx=0.0
397     c endif
398     yy0=xco2*GHGBGR(1)
399     xco2ann=xco2ann+yy0
400     c yy0 and yy CO2 in PPM, xx in GtC/year, ocu and tcu in GtC/month
401     c dtemi=1./12.
402     c print *,'ocu=',ocu,' tcu=',tcu
403     c ocu=1.25*ocu
404     c tcu=1.8*tcu
405     print *,'ocu=',ocu,' tcu=',tcu
406     print *,'emi=',xx*dtemi
407     yy=yy0+(xx*dtemi-ocu-tcu)/2.1
408     xco2=yy/GHGBGR(1)
409     c if(ncall.eq.2)then
410     print *,'EMISSIPCC '
411     print *,' year=',year
412     print *,'YEAR0=',YEAR0
413     print *,yy0,xx
414     print *,ocu,tcu
415     print *,yy,xco2
416     do 30 j=1,jm0
417     atm_co2(j)=yy
418     30 continue
419     c stop
420     c endif
421     if(ncall.lt.3)ncall=ncall+1
422     return
423     end
424    

  ViewVC Help
Powered by ViewVC 1.1.22