116 module module_radiation_gases
122 & kind_phys, kind_io4
123 use funcphys
, only : fpkapx
124 use physcons
, only :
con_pi
125 use ozne_def
, only : jmr => latsozc, loz => levozc, &
126 & blte => blatc, dlte=> dphiozc, &
128 use module_iounitdef
, only : nio3clm, nico2cn
135 character(40),
parameter :: &
136 & VTAGGAS=
'NCEP-Radiation_gases v5.1 Nov 2012 '
151 real (kind=kind_phys),
parameter ::
resco2=15.0
155 real (kind=kind_phys),
parameter ::
prsco2=788.0
161 real (kind=kind_phys),
parameter :: co2vmr_def = 350.0e-6
162 real (kind=kind_phys),
parameter :: n2ovmr_def = 0.31e-6
163 real (kind=kind_phys),
parameter :: ch4vmr_def = 1.50e-6
164 real (kind=kind_phys),
parameter :: o2vmr_def = 0.209
165 real (kind=kind_phys),
parameter :: covmr_def = 1.50e-8
189 real (kind=kind_phys),
allocatable :: pkstr(:), o3r(:,:,:)
190 integer :: k1oz = 0, k2oz = 0
191 real (kind=kind_phys) :: facoz = 0.0
195 real (kind=kind_phys),
allocatable :: co2vmr_sav(:,:,:)
196 real (kind=kind_phys),
allocatable :: co2cyc_sav(:,:,:)
198 real (kind=kind_phys) :: co2_glb = co2vmr_def
199 real (kind=kind_phys) :: gco2cyc(12)
200 data gco2cyc(:) / 12*0.0 /
202 integer :: kyrsav = 0
203 integer :: kmonsav = 1
270 integer,
intent(in) :: me
275 real (kind=kind_phys),
dimension(IMXCO2,JMXCO2) :: co2dat
276 real (kind=kind_phys) :: co2g1, co2g2
277 real (kind=kind_phys) :: pstr(loz)
278 real (kind=kind_io4) :: o3clim4(jmr,loz,12), pstr4(loz)
280 integer :: imond(12), ilat(jmr,12)
281 integer :: i, j, k, iyr, imo
282 logical :: file_exist, lextpl
283 character :: cline*100, cform*8
284 data cform /
'(24f7.2)' /
288 if ( me == 0 ) print *, vtaggas
297 print *,
' - Using interactive ozone distribution'
300 if ( timeozc /= 12 )
then
301 print *,
' - Using climatology ozone distribution'
302 print *,
' timeozc=',timeozc,
' is not monthly mean', &
303 &
' - job aborting in subroutin gas_init!!!'
307 allocate (pkstr(loz), o3r(jmr,loz,12))
310 if ( loz == 17 )
then
312 read (nio3clm,15) pstr4(k)
318 read (nio3clm,16) imond(imo), ilat(j,imo), &
319 & (o3clim4(j,k,imo),k=1,10)
320 16
format(i2,i4,10f6.2)
321 read (nio3clm,20) (o3clim4(j,k,imo),k=11,loz)
328 read (nio3clm) pstr4(k)
333 read (nio3clm) (o3clim4(j,k,imo),j=1,jmr)
341 o3r(j,k,imo) = o3clim4(j,k,imo) * 1.655e-6
351 print *,
' - Using climatology ozone distribution'
352 print *,
' Found ozone data for levels pstr=', &
358 pkstr(k) = fpkapx(pstr(k)*100.0)
366 lab_ico2 :
if (
ico2flg == 0 )
then
369 print *,
' - Using prescribed co2 global mean value=', &
375 lab_ictm :
if (
ictmflg == -1 )
then
378 if ( .not. file_exist )
then
379 print *,
' Can not find user CO2 data file: ',
co2usr_file, &
380 &
' - Stopped in subroutine gas_init !!'
384 open(nico2cn,file=
co2usr_file,form=
'formatted',status=
'old')
386 read (nico2cn, 25) iyr, cline, co2g1, co2g2
387 25
format(i4,a94,f7.2,16x,f5.2)
388 co2_glb = co2g1 * 1.0e-6
392 print *,
' - Using co2 global annual mean value from', &
394 print *, iyr,cline(1:94),co2g1,
' GROWTH RATE =', co2g2
400 read (nico2cn,cform) co2dat
405 co2vmr_sav(i,j,imo) = co2dat(i,j) * 1.0e-6
411 print *,
' - Using co2 monthly 2-d data from user', &
413 print *, iyr,cline(1:94),co2g1,
' GROWTH RATE =', co2g2
415 print *,
' CHECK: Sample of selected months of CO2 data'
417 print *,
' Month =',imo
418 print *, co2vmr_sav(1,:,imo)
422 print *,
' ICO2=',
ico2flg,
' is not a valid selection', &
423 &
' - Stoped in subroutine gas_init!!!'
434 print *,
' - Using observed co2 global annual mean value'
440 print *,
' - Using observed co2 monthly 2-d data'
443 print *,
' ICO2=',
ico2flg,
' is not a valid selection', &
444 &
' - Stoped in subroutine gas_init!!!'
450 if ( .not. file_exist )
then
452 print *,
' Can not find seasonal cycle CO2 data: ', &
453 &
co2cyc_file,
' - Stopped in subroutine gas_init !!'
464 read (nico2cn, 35) cline, co2g1, co2g2
465 35
format(a98,f7.2,16x,f5.2)
466 read (nico2cn,cform) co2dat
469 print *,
' - Superimpose seasonal cycle to mean CO2 data'
470 print *,
' Opened CO2 climatology seasonal cycle data',&
476 read (nico2cn,45) cline, gco2cyc(imo)
479 gco2cyc(imo) = gco2cyc(imo) * 1.0e-6
481 read (nico2cn,cform) co2dat
485 co2cyc_sav(i,j,imo) = co2dat(i,j) * 1.0e-6
516 & ( iyear, imon, iday, ihour, loz1st, ldoco2, me )
578 integer,
intent(in) :: iyear, imon, iday, ihour, me
580 logical,
intent(in) :: loz1st, ldoco2
585 real (kind=kind_phys),
dimension(IMXCO2,JMXCO2) :: co2dat, co2ann
586 real (kind=kind_phys) :: co2g1, co2g2, rate
588 integer :: i, id, j, l, iyr, imo, iyr1, iyr2, jyr, idyr
589 integer,
save :: mdays(13), midmon=15, midm=15, midp=45
591 data mdays / 31,28,31,30,31,30,31,31,30,31,30,31,30 /
593 logical :: file_exist, lextpl, change
594 character :: cline*100, cform*8, cfile1*26
595 data cform /
'(24f7.2)' /
602 midmon = mdays(imon)/2 + 1
603 change = loz1st .or. ( (iday==midmon) .and. (ihour==0) )
606 if ( iday < midmon )
then
607 k1oz = mod(imon+10, 12) + 1
608 midm = mdays(k1oz)/2 + 1
610 midp = mdays(k1oz) + midmon
614 k2oz = mod(imon, 12) + 1
615 midp = mdays(k2oz)/2 + 1 + mdays(k1oz)
619 if (iday < midmon)
then
620 id = iday + mdays(k1oz)
625 facoz = float(id - midm) / float(midp - midm)
632 if ( .not. ldoco2 )
return
638 lextpl = ( mod(
ictmflg,10) == 1 )
640 if ( idyr == 0 ) idyr = iyear
646 if ( kyrsav == iyear )
return
657 print *,
' Requested CO2 data year',iyear,
' earlier than', &
659 print *,
' Which is the earliest monthly observation', &
661 print *,
' Thus, historical global mean data is used'
667 if ( .not. file_exist )
then
668 print *,
' Requested co2 data file "',
co2gbl_file, &
669 &
'" not found - Stopped in subroutine gas_update!!'
673 open (nico2cn,file=
co2gbl_file,form=
'formatted',status=
'old')
676 read (nico2cn, 24) iyr1, iyr2, cline
677 24
format(i4,4x,i4,a48)
684 if ( idyr < iyr1 )
then
692 lab_dowhile1 :
do while ( i >= iyr1 )
695 read (nico2cn, *) jyr, co2g1, co2g2
697 if ( i == iyr .and. iyr == jyr )
then
698 co2_glb = (co2g1+co2g2) * 0.5e-6
702 co2vmr_sav(i,j,1:6) = co2g1 * 1.0e-6
703 co2vmr_sav(i,j,7:12) = co2g2 * 1.0e-6
708 if ( me == 0 ) print *,
' Co2 data for year',iyear, &
725 write(cfile1(19:22),34) idyr
730 inquire (file=cfile1, exist=file_exist)
731 if ( .not. file_exist )
then
733 lab_if_ictm :
if (
ictmflg > 10 )
then
735 print *,
' Specified co2 data for year',idyr, &
736 &
' not found !! Need to change namelist ICTM !!'
737 print *,
' *** Stopped in subroutine gas_update !!'
742 print *,
' Requested co2 data for year',idyr, &
743 &
' not found, check for other available data set'
746 lab_dowhile2 :
do while ( iyr >=
minyear )
748 write(cfile1(19:22),34) iyr
750 inquire (file=cfile1, exist=file_exist)
752 print *,
' Looking for CO2 file ',cfile1
755 if ( file_exist )
then
760 if ( .not. file_exist )
then
762 print *,
' Can not find co2 data source file'
763 print *,
' *** Stopped in subroutine gas_update !!'
773 open (nico2cn,file=cfile1,form=
'formatted',status=
'old')
775 read (nico2cn, 36) iyr, cline, co2g1, co2g2
776 36
format(i4,a94,f7.2,16x,f5.2)
779 print *,
' Opened co2 data file: ',cfile1
780 print *, iyr, cline(1:94), co2g1,
' GROWTH RATE =', co2g2
787 rate = 2.00 * (iyear - iyr)
792 co2_glb = (co2g1 + rate) * 1.0e-6
794 print *,
' Global annual mean CO2 data for year', &
802 print *,
' CHECK: Monthly deviations of climatology ', &
803 &
'to be superimposed on global annual mean'
810 read (nico2cn,cform) co2dat
815 co2ann(i,j) = co2ann(i,j) + co2dat(i,j)
822 co2ann(i,j) = co2ann(i,j) * 1.0e-6 / float(12)
829 co2vmr_sav(i,j,imo) = co2ann(i,j)+co2cyc_sav(i,j,imo)
835 print *,
' CHECK: Sample of 2-d annual mean of CO2 ', &
836 &
'data used for year:',iyear
838 print *,
' CHECK: AFTER adding seasonal cycle, Sample ', &
839 &
'of selected months of CO2 data for year:',iyear
841 print *,
' Month =',imo
842 print *, co2vmr_sav(1,:,imo)
851 read (nico2cn,cform) co2dat
856 co2vmr_sav(i,j,imo) = (co2dat(i,j) + rate) * 1.0e-6
862 print *,
' CHECK: Sample of selected months of CO2 ', &
863 &
'data used for year:',iyear
865 print *,
' Month =',imo
866 print *, co2vmr_sav(1,:,imo)
909 & ( plvl, xlon, xlat, &
969 integer,
intent(in) :: IMAX, LMAX
970 real (kind=kind_phys),
intent(in) :: plvl(:,:), xlon(:), xlat(:)
973 real (kind=kind_phys),
intent(out) :: gasdat(:,:,:)
976 integer :: i, k, ilat, ilon
978 real (kind=kind_phys) :: xlon1, xlat1, tmp
986 gasdat(i,k,1) = co2vmr_def
987 gasdat(i,k,2) = n2ovmr_def
988 gasdat(i,k,3) = ch4vmr_def
989 gasdat(i,k,4) = o2vmr_def
990 gasdat(i,k,5) = covmr_def
1006 gasdat(i,k,1) = co2_glb + gco2cyc(kmonsav)
1017 if ( xlon1 < 0.0 ) xlon1 = xlon1 +
con_pi
1018 xlat1 =
hfpi - xlat(i)
1021 ilon = min(
imxco2, int( xlon1*tmp + 1 ))
1022 ilat = min(
jmxco2, int( xlat1*tmp + 1 ))
1026 if ( plvl(i,k) >=
prsco2 )
then
1027 gasdat(i,k,1) = co2vmr_sav(ilon,ilat,kmonsav)
1029 gasdat(i,k,1) = co2_glb + gco2cyc(kmonsav)
1034 if ( plvl(i,k+1) >=
prsco2 )
then
1035 gasdat(i,k,1) = co2vmr_sav(ilon,ilat,kmonsav)
1037 gasdat(i,k,1) = co2_glb + gco2cyc(kmonsav)
1092 integer,
intent(in) :: IMAX, LM
1094 real (kind=kind_phys),
intent(in) :: prslk(:,:), xlat(:)
1097 real (kind=kind_phys),
intent(out) :: o3mmr(:,:)
1100 real (kind=kind_phys) :: o3i(imax,loz), wk1(imax), deglat, elte, &
1101 & tem, tem1, tem2, tem3, tem4, temp
1102 integer :: i, j, k, l, j1, j2, ll
1106 elte = blte + (jmr-1)*dlte
1109 deglat = xlat(i) *
raddeg
1112 if (deglat > blte .and. deglat < elte)
then
1113 tem1 = (deglat - blte) / dlte + 1
1117 elseif (deglat <= blte)
then
1121 elseif (deglat >= elte)
then
1129 tem3 = tem2*o3r(j1,j,k1oz) + tem1*o3r(j2,j,k1oz)
1130 tem4 = tem2*o3r(j1,j,k2oz) + tem1*o3r(j2,j,k2oz)
1131 o3i(i,j) = tem4*facoz + tem3*(1.0 - facoz)
1137 if (
ivflip == 1) ll = lm -l + 1
1140 wk1(i) = prslk(i,ll)
1144 temp = 1.0 / (pkstr(k+1) - pkstr(k))
1147 if (wk1(i) > pkstr(k) .and. wk1(i) <= pkstr(k+1))
then
1148 tem = (pkstr(k+1) - wk1(i)) * temp
1149 o3mmr(i,ll) = tem * o3i(i,k) + (1.0 - tem) * o3i(i,k+1)
1155 if (wk1(i) > pkstr(loz)) o3mmr(i,ll) = o3i(i,loz)
1156 if (wk1(i) < pkstr(1)) o3mmr(i,ll) = o3i(i,1)
1167 end module module_radiation_gases
character, save co2dat_file
external co2 2d monthly obsv data table: co2historicaldata_2004.txt
real(kind=kind_phys), parameter con_pi
pi
integer, parameter imxco2
input co2 dat lon points
real(kind=kind_phys), parameter resco2
horizontal resolution in degree
character, save co2gbl_file
external co2 global annual mean data tb: co2historicaldata_glob.txt
subroutine, public gas_update(iyear, imon, iday, ihour, loz1st, ldoco2, me)
This subroutine reads in 2-d monthly co2 data set for a specified year. Data are in a 15 degree lat/l...
character, save co2usr_file
external co2 user defined data table: co2userdata.txt
real(kind=kind_phys), parameter f22vmr_def
aer 2003 value
real(kind=kind_phys), parameter cl4vmr_def
aer 2003 value
integer, save ico2flg
co2 data source control flag =0:prescribed value(380 ppmv) =1:yearly global averaged annual mean ...
real(kind=kind_phys), parameter prsco2
pressure limitation for 2-d co2 (mb)
real(kind=kind_phys), parameter f12vmr_def
aer 2003 value
real(kind=kind_phys), parameter f11vmr_def
aer 2003 value
subroutine, public gas_init(me)
This subroutine sets up ozone, co2, etc. parameters. If climatology ozone then read in monthly ozone ...
subroutine, public getgases(plvl, xlon, xlat, IMAX, LMAX, gasdat )
This subroutine sets up global distribution of radiation absorbing gases in volume mixing ratio...
subroutine, public getozn(prslk, xlat, IMAX, LM, o3mmr )
This subroutine sets up climatological ozone profile for radiation calculation. This code is original...
integer, save ioznflg
ozone data source control flag =0:use seasonal climatology ozone data >0:use prognostic ozone sch...
integer, parameter minyear
earlist year 2-d co2 data available
character, save co2cyc_file
external co2 clim monthly cycle data tb: co2monthlycyc.txt
integer, save ictmflg
controls external data at initial time and data usage during forecast time =-2:as in 0...
integer, parameter jmxco2
input co2 data lat points
real(kind=kind_phys), parameter raddeg
rad->deg conversion
real(kind=kind_phys), parameter f113vmr_def
gfdl 1999 value
integer, parameter, public nf_vgas
number of gas species
integer, save ivflip
vertical profile indexing flag
real(kind=kind_phys), parameter hfpi
half of pi