Interoperable Physics Driver for NGGPS
rad_initialize.f
Go to the documentation of this file.
1 !-----------------------------------
2  subroutine rad_initialize &
3 !...................................
4 ! --- inputs:
5  & ( si,levr,ictm,isol,ico2,iaer,ialb,iems,ntcw, &
6  & num_p3d,npdf3d,ntoz,iovr_sw,iovr_lw,isubc_sw,isubc_lw, &
7  & crick_proof,ccnorm,norad_precip, &
8  & idate,iflip,me )
9 ! --- outputs: ( none )
10 
11 ! ================= subprogram documentation block ================ !
12 ! !
13 ! subprogram: rad_initialize - a subprogram to initialize radiation !
14 ! !
15 ! usage: call rad_initialize !
16 ! !
17 ! attributes: !
18 ! language: fortran 90 !
19 ! !
20 ! program history: !
21 ! mar 2012 - yu-tai hou create the program to initialize fixed !
22 ! control variables for radiaion processes. this !
23 ! subroutine is called at the start of model run. !
24 ! nov 2012 - yu-tai hou modified control parameter through !
25 ! module 'physparam'. !
26 ! mar 2014 - sarah lu iaermdl is determined from iaer !
27 ! jul 2014 - s moorthi add npdf3d for pdf clouds !
28 ! !
29 ! ==================== defination of variables ==================== !
30 ! !
31 ! input parameters: !
32 ! si : model vertical sigma interface or equivalence !
33 ! levr : number of model vertical layers !
34 ! ictm :=yyyy#, external data time/date control flag !
35 ! = -2: same as 0, but superimpose seasonal cycle !
36 ! from climatology data set. !
37 ! = -1: use user provided external data for the !
38 ! forecast time, no extrapolation. !
39 ! = 0: use data at initial cond time, if not !
40 ! available, use latest, no extrapolation. !
41 ! = 1: use data at the forecast time, if not !
42 ! available, use latest and extrapolation. !
43 ! =yyyy0: use yyyy data for the forecast time, !
44 ! no further data extrapolation. !
45 ! =yyyy1: use yyyy data for the fcst. if needed, do !
46 ! extrapolation to match the fcst time. !
47 ! isol := 0: use the old fixed solar constant in "physcon"!
48 ! =10: use the new fixed solar constant in "physcon"!
49 ! = 1: use noaa ann-mean tsi tbl abs-scale data tabl!
50 ! = 2: use noaa ann-mean tsi tbl tim-scale data tabl!
51 ! = 3: use cmip5 ann-mean tsi tbl tim-scale data tbl!
52 ! = 4: use cmip5 mon-mean tsi tbl tim-scale data tbl!
53 ! ico2 :=0: use prescribed global mean co2 (old oper) !
54 ! =1: use observed co2 annual mean value only !
55 ! =2: use obs co2 monthly data with 2-d variation !
56 ! iaer : 4-digit aerosol flag (dabc for aermdl,volc,lw,sw)!
57 ! d: =0 or none, opac-climatology aerosol scheme !
58 ! =1 use gocart climatology aerosol scheme !
59 ! =2 use gocart progostic aerosol scheme !
60 ! a: =0 use background stratospheric aerosol !
61 ! =1 incl stratospheric vocanic aeros !
62 ! b: =0 no topospheric aerosol in lw radiation !
63 ! =1 include tropspheric aerosols for lw !
64 ! c: =0 no topospheric aerosol in sw radiation !
65 ! =1 include tropspheric aerosols for sw !
66 ! ialb : control flag for surface albedo schemes !
67 ! =0: climatology, based on surface veg types !
68 ! =1: modis retrieval based surface albedo scheme !
69 ! iems : ab 2-digit control flag !
70 ! a: =0 set sfc air/ground t same for lw radiation !
71 ! =1 set sfc air/ground t diff for lw radiation !
72 ! b: =0 use fixed sfc emissivity=1.0 (black-body) !
73 ! =1 use varying climtology sfc emiss (veg based)!
74 ! =2 future development (not yet) !
75 ! ntcw :=0 no cloud condensate calculated !
76 ! >0 array index location for cloud condensate !
77 ! num_p3d :=3: ferrier's microphysics cloud scheme !
78 ! =4: zhao/carr/sundqvist microphysics cloud !
79 ! npdf3d =0 no pdf clouds !
80 ! =3 (when num_p3d=4) pdf clouds with zhao/carr/ !
81 ! sundqvist scheme !
82 ! ntoz : ozone data control flag !
83 ! =0: use climatological ozone profile !
84 ! >0: use interactive ozone profile !
85 ! iovr_sw/iovr_lw : control flag for cloud overlap (sw/lw rad) !
86 ! =0: random overlapping clouds !
87 ! =1: max/ran overlapping clouds !
88 ! isubc_sw/isubc_lw: sub-column cloud approx control flag (sw/lw rad) !
89 ! =0: with out sub-column cloud approximation !
90 ! =1: mcica sub-col approx. prescribed random seed !
91 ! =2: mcica sub-col approx. provided random seed !
92 ! crick_proof : control flag for eliminating CRICK !
93 ! ccnorm : control flag for in-cloud condensate mixing ratio!
94 ! norad_precip : control flag for not using precip in radiation !
95 ! idate(4) : ncep absolute date and time of initial condition !
96 ! (hour, month, day, year) !
97 ! iflip : control flag for direction of vertical index !
98 ! =0: index from toa to surface !
99 ! =1: index from surface to toa !
100 ! me : print control flag !
101 ! !
102 ! subroutines called: radinit !
103 ! !
104 ! =================================================================== !
105 !
106  use physparam, only : isolar , ictmflg, ico2flg, ioznflg, iaerflg,&
108  & iovrsw , iovrlw , lcrick , lcnorm , lnoprec, &
110  & kind_phys
111 
112  use module_radiation_driver, only : radinit
113 !
114  implicit none
115 
116 ! --- input:
117  integer, intent(in) :: levr, ictm, isol, ico2, iaer, &
118  & ntcw, ialb, iems, num_p3d, npdf3d, ntoz, iovr_sw, iovr_lw, &
119  & isubc_sw, isubc_lw, iflip, me, idate(4)
120 
121  real (kind=kind_phys), intent(in) :: si(levr+1)
122 
123  logical, intent(in) :: crick_proof, ccnorm, norad_precip
124 
125 ! --- output: ( none )
126 
127 ! --- local:
128  integer :: icld
129 !
130 !===> ... start here
131 !
132 ! --- set up parameters for radiation initialization
133 
134  isolar = isol ! solar constant control flag
135 
136  ictmflg= ictm ! data ic time/date control flag
137  ico2flg= ico2 ! co2 data source control flag
138  ioznflg= ntoz ! ozone data source control flag
139 
140  if ( ictm==0 .or. ictm==-2 ) then
141  iaerflg = mod(iaer, 100) ! no volcanic aerosols for clim hindcast
142  else
143  iaerflg = mod(iaer, 1000)
144  endif
145  laswflg= (mod(iaerflg,10) > 0) ! control flag for sw tropospheric aerosol
146  lalwflg= (mod(iaerflg/10,10) > 0) ! control flag for lw tropospheric aerosol
147  lavoflg= (iaerflg >= 100) ! control flag for stratospheric volcanic aeros
148  iaermdl = iaer/1000 ! control flag for aerosol scheme selection
149  if ( iaermdl < 0 .or. iaermdl > 2) then
150  print *, ' Error -- IAER flag is incorrect, Abort'
151  stop 7777
152  endif
153 
154  if ( ntcw > 0 ) then
155  icldflg = 1 ! prognostic cloud optical prop scheme
156  else
157  icldflg = 0 ! diagnostic cloud optical prop scheme
158  endif
159  icmphys = 1 ! default
160  if ( num_p3d == 4 ) then
161  if (npdf3d /= 3) then
162  icmphys = 1 ! zhao/moorthi's prognostic cloud scheme
163  else
164  icmphys = 3 ! zhao+ pdf cloud & cnvc and cnvw
165  endif
166  elseif ( num_p3d == 3 ) then
167  icmphys = 2 ! ferrier's microphysics
168  endif
169 ! if (ncld == 2) icmphys = 1 ! MG 2m Morrison scheme
170 !
171  iovrsw = iovr_sw ! cloud overlapping control flag for sw
172  iovrlw = iovr_lw ! cloud overlapping control flag for lw
173 
174  lcrick = crick_proof ! control flag for eliminating CRICK
175  lcnorm = ccnorm ! control flag for in-cld condensate
176  lnoprec = norad_precip ! precip effect on radiation flag (ferrier microphysics)
177  isubcsw = isubc_sw ! sub-column cloud approx flag in sw radiation
178  isubclw = isubc_lw ! sub-column cloud approx flag in lw radiation
179 
180  ialbflg= ialb ! surface albedo control flag
181  iemsflg= iems ! surface emissivity control flag
182 
183  ivflip = iflip ! vertical index direction control flag
184 
185 ! --- assign initial permutation seed for mcica cloud-radiation
186  if ( isubc_sw>0 .or. isubc_lw>0 ) then
187 ! ipsd0 = 17*idate(1)+43*idate(2)+37*idate(3)+23*idate(4) + ipsd0
188  ipsd0 = 17*idate(1)+43*idate(2)+37*idate(3)+23*idate(4)
189  endif
190 
191  if ( me == 0 ) then
192  print *,' In rad_initialize, before calling radinit'
193  print *,' si =',si
194  print *,' levr=',levr,' ictm=',ictm,' isol=',isol,' ico2=',ico2,&
195  & ' iaer=',iaer,' ialb=',ialb,' iems=',iems,' ntcw=',ntcw
196  print *,' np3d=',num_p3d,' ntoz=',ntoz,' iovr_sw=',iovr_sw, &
197  & ' iovr_lw=',iovr_lw,' isubc_sw=',isubc_sw, &
198  & ' isubc_lw=',isubc_lw,' iflip=',iflip,' me=',me
199  print *,' crick_proof=',crick_proof, &
200  & ' ccnorm=',ccnorm,' norad_precip=',norad_precip
201  endif
202 
203  call radinit &
204 ! --- inputs:
205  & ( si, levr, me )
206 ! --- outputs:
207 ! ( none )
208 
209  if ( me == 0 ) then
210  print *,' Radiation sub-cloud initial seed =',ipsd0, &
211  & ' IC-idate =',idate
212  print *,' return from rad_initialize - after calling radinit'
213  endif
214 !
215  return
216 !...................................
217  end subroutine rad_initialize
218 !-----------------------------------
integer, save iovrsw
cloud overlapping control flag for SW
Definition: physparam.f:192
integer, save isubcsw
sub-column cloud approx flag in SW radiation
Definition: physparam.f:224
integer, save iaermdl
aerosol model scheme control flag
Definition: physparam.f:146
logical, save lalwflg
LW aerosols effect control flag.
Definition: physparam.f:150
integer, save iaerflg
aerosol effect control flag
Definition: physparam.f:148
logical, save lcnorm
in-cld condensate control flag
Definition: physparam.f:198
logical, save lcrick
eliminating CRICK control flag
Definition: physparam.f:196
integer, save ialbflg
surface albedo scheme control flag
Definition: physparam.f:209
subroutine rad_initialize
Definition: rad_initialize.f:4
integer, save ico2flg
co2 data source control flag
Definition: physparam.f:165
integer, save icmphys
cloud micorphysics scheme control flag
Definition: physparam.f:190
integer, save icldflg
cloud optical property scheme control flag
Definition: physparam.f:188
integer, save iemsflg
surface emissivity scheme control flag
Definition: physparam.f:211
logical, save laswflg
SW aerosols effect control flag.
Definition: physparam.f:152
logical, save lnoprec
precip effect on radiation flag (Ferrier microphysics)
Definition: physparam.f:200
subroutine, public radinit(si, NLAY, me)
This subroutine is the initialization of radiation calculations.
Definition: grrad.f:386
integer, save ioznflg
ozone data source control flag
Definition: physparam.f:169
integer, save ictmflg
external data time/date control flag
Definition: physparam.f:167
integer, save isolar
solar constant scheme control flag
Definition: physparam.f:134
integer, save ipsd0
initial permutaion seed for mcica radiation
Definition: physparam.f:228
integer, save isubclw
sub-column cloud approx flag in LW radiation
Definition: physparam.f:226
integer, save ivflip
vertical profile indexing flag
Definition: physparam.f:222
integer, save iovrlw
cloud overlapping control flag for LW
Definition: physparam.f:194
logical, save lavoflg
stratospheric volcanic effect flag
Definition: physparam.f:154