source: palm/trunk/SOURCE/radiation_model.f90 @ 1757

Last change on this file since 1757 was 1757, checked in by maronga, 8 years ago

some changes in land surface model, radiation model, nudging and some minor updates

  • Property svn:keywords set to Id
File size: 69.0 KB
RevLine 
[1682]1!> @file radiation_model.f90
[1496]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1585]16! Copyright 1997-2015 Leibniz Universitaet Hannover
[1496]17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
[1757]21! Added parameter unscheduled_radiation_calls. Bugfix: interpolation of sounding
22! profiles for pressure and temperature above the LES domain.
[1496]23!
24! Former revisions:
25! -----------------
26! $Id: radiation_model.f90 1757 2016-02-22 15:49:32Z maronga $
27!
[1710]28! 1709 2015-11-04 14:47:01Z maronga
29! Bugfix: set initial value for rrtm_lwuflx_dt to zero, small formatting
30! corrections
31!
[1702]32! 1701 2015-11-02 07:43:04Z maronga
33! Bugfixes: wrong index for output of timeseries, setting of nz_snd_end
34!
[1692]35! 1691 2015-10-26 16:17:44Z maronga
36! Added option for spin-up runs without radiation (skip_time_do_radiation). Bugfix
37! in calculation of pressure profiles. Bugfix in calculation of trace gas profiles.
38! Added output of radiative heating rates.
39!
[1683]40! 1682 2015-10-07 23:56:08Z knoop
41! Code annotations made doxygen readable
42!
[1607]43! 1606 2015-06-29 10:43:37Z maronga
44! Added preprocessor directive __netcdf to allow for compiling without netCDF.
45! Note, however, that RRTMG cannot be used without netCDF.
46!
[1591]47! 1590 2015-05-08 13:56:27Z maronga
48! Bugfix: definition of character strings requires same length for all elements
49!
[1588]50! 1587 2015-05-04 14:19:01Z maronga
51! Added albedo class for snow
52!
[1586]53! 1585 2015-04-30 07:05:52Z maronga
54! Added support for RRTMG
55!
[1572]56! 1571 2015-03-12 16:12:49Z maronga
57! Added missing KIND attribute. Removed upper-case variable names
58!
[1552]59! 1551 2015-03-03 14:18:16Z maronga
60! Added support for data output. Various variables have been renamed. Added
61! interface for different radiation schemes (currently: clear-sky, constant, and
62! RRTM (not yet implemented).
63!
[1497]64! 1496 2014-12-02 17:25:50Z maronga
65! Initial revision
66!
[1496]67!
68! Description:
69! ------------
[1682]70!> Radiation models and interfaces
71!> @todo move variable definitions used in init_radiation only to the subroutine
72!>       as they are no longer required after initialization.
73!> @todo Output of full column vertical profiles used in RRTMG
74!> @todo Output of other rrtm arrays (such as volume mixing ratios)
75!> @todo Adapt for use with topography
76!>
77!> @note Many variables have a leading dummy dimension (0:0) in order to
78!>       match the assume-size shape expected by the RRTMG model.
[1496]79!------------------------------------------------------------------------------!
[1682]80 MODULE radiation_model_mod
81 
[1496]82
83    USE arrays_3d,                                                             &
[1691]84        ONLY:  dzw, hyp, pt, q, ql, zw
[1496]85
[1585]86    USE cloud_parameters,                                                      &
[1691]87        ONLY:  cp, l_d_cp, nc_const, rho_l, sigma_gc 
[1585]88
89    USE constants,                                                             &
90        ONLY:  pi
91
[1496]92    USE control_parameters,                                                    &
[1585]93        ONLY:  cloud_droplets, cloud_physics, g, initializing_actions,         &
[1691]94               large_scale_forcing, lsf_surf, phi, pt_surface, rho_surface,    &
[1585]95               surface_pressure, time_since_reference_point
[1496]96
97    USE indices,                                                               &
[1585]98        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb_s_inner, nzb, nzt
[1496]99
100    USE kinds
101
[1606]102#if defined ( __netcdf )
[1585]103    USE netcdf
[1606]104#endif
[1585]105
[1551]106    USE netcdf_control,                                                        &
107        ONLY:  dots_label, dots_num, dots_unit
[1496]108
[1585]109#if defined ( __rrtmg )
110    USE parrrsw,                                                               &
111        ONLY:  naerec, nbndsw
[1551]112
[1585]113    USE parrrtm,                                                               &
114        ONLY:  nbndlw
115
116    USE rrtmg_lw_init,                                                         &
117        ONLY:  rrtmg_lw_ini
118
119    USE rrtmg_sw_init,                                                         &
120        ONLY:  rrtmg_sw_ini
121
122    USE rrtmg_lw_rad,                                                          &
123        ONLY:  rrtmg_lw
124
125    USE rrtmg_sw_rad,                                                          &
126        ONLY:  rrtmg_sw
127#endif
128
129
130
[1496]131    IMPLICIT NONE
132
[1585]133    CHARACTER(10) :: radiation_scheme = 'clear-sky' ! 'constant', 'clear-sky', or 'rrtmg'
[1551]134
[1585]135!
136!-- Predefined Land surface classes (albedo_type) after Briegleb (1992)
[1590]137    CHARACTER(37), DIMENSION(0:16), PARAMETER :: albedo_type_name = (/      &
138                                   'user defined                         ', & !  0
139                                   'ocean                                ', & !  1
140                                   'mixed farming, tall grassland        ', & !  2
141                                   'tall/medium grassland                ', & !  3
142                                   'evergreen shrubland                  ', & !  4
143                                   'short grassland/meadow/shrubland     ', & !  5
144                                   'evergreen needleleaf forest          ', & !  6
145                                   'mixed deciduous evergreen forest     ', & !  7
146                                   'deciduous forest                     ', & !  8
147                                   'tropical evergreen broadleaved forest', & !  9
148                                   'medium/tall grassland/woodland       ', & ! 10
149                                   'desert, sandy                        ', & ! 11
150                                   'desert, rocky                        ', & ! 12
151                                   'tundra                               ', & ! 13
152                                   'land ice                             ', & ! 14
153                                   'sea ice                              ', & ! 15
154                                   'snow                                 '  & ! 16
[1585]155                                                         /)
[1496]156
[1682]157    INTEGER(iwp) :: albedo_type  = 5,    & !< Albedo surface type (default: short grassland)
158                    day,                 & !< current day of the year
159                    day_init     = 172,  & !< day of the year at model start (21/06)
160                    dots_rad     = 0       !< starting index for timeseries output
[1496]161
162
163
[1585]164
165
166
[1757]167    LOGICAL ::  unscheduled_radiation_calls = .TRUE., & !< flag parameter indicating whether additional calls of the radiation code are allowed
168                constant_albedo = .FALSE.,            & !< flag parameter indicating whether the albedo may change depending on zenith
169                force_radiation_call = .FALSE.,       & !< flag parameter for unscheduled radiation calls
170                lw_radiation = .TRUE.,                & !< flag parameter indicating whether longwave radiation shall be calculated
171                radiation = .FALSE.,                  & !< flag parameter indicating whether the radiation model is used
172                sun_up    = .TRUE.,                   & !< flag parameter indicating whether the sun is up or down
173                sw_radiation = .TRUE.                   !< flag parameter indicing whether shortwave radiation shall be calculated
[1585]174
[1496]175
[1691]176    REAL(wp), PARAMETER :: d_seconds_hour  = 0.000277777777778_wp,  & !< inverse of seconds per hour (1/3600)
177                           d_hours_day    = 0.0416666666667_wp,     & !< inverse of hours per day (1/24)
178                           sigma_sb       = 5.67037321E-8_wp,       & !< Stefan-Boltzmann constant
179                           solar_constant = 1368.0_wp                 !< solar constant at top of atmosphere
[1585]180
[1691]181    REAL(wp) :: albedo = 9999999.9_wp,           & !< NAMELIST alpha
182                albedo_lw_dif = 9999999.9_wp,    & !< NAMELIST aldif
183                albedo_lw_dir = 9999999.9_wp,    & !< NAMELIST aldir
184                albedo_sw_dif = 9999999.9_wp,    & !< NAMELIST asdif
185                albedo_sw_dir = 9999999.9_wp,    & !< NAMELIST asdir
186                decl_1,                          & !< declination coef. 1
187                decl_2,                          & !< declination coef. 2
188                decl_3,                          & !< declination coef. 3
189                dt_radiation = 0.0_wp,           & !< radiation model timestep
190                emissivity = 0.98_wp,            & !< NAMELIST surface emissivity
191                lambda = 0.0_wp,                 & !< longitude in degrees
192                lon = 0.0_wp,                    & !< longitude in radians
193                lat = 0.0_wp,                    & !< latitude in radians
194                net_radiation = 0.0_wp,          & !< net radiation at surface
195                skip_time_do_radiation = 0.0_wp, & !< Radiation model is not called before this time
196                sky_trans,                       & !< sky transmissivity
197                time_radiation = 0.0_wp,         & !< time since last call of radiation code
198                time_utc,                        & !< current time in UTC
199                time_utc_init = 43200.0_wp         !< UTC time at model start (noon)
200
[1682]201    REAL(wp), DIMENSION(0:0) ::  zenith        !< solar zenith angle
[1585]202
[1496]203    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: &
[1682]204                alpha,                       & !< surface broadband albedo (used for clear-sky scheme)
[1709]205                rad_lw_out_change_0,         & !< change in LW out due to change in surface temperature
[1682]206                rad_net,                     & !< net radiation at the surface
207                rad_net_av                     !< average of rad_net
[1496]208
[1585]209!
210!-- Land surface albedos for solar zenith angle of 60° after Briegleb (1992)     
211!-- (shortwave, longwave, broadband):   sw,      lw,      bb,
[1587]212    REAL(wp), DIMENSION(0:2,1:16), PARAMETER :: albedo_pars = RESHAPE( (/& 
[1585]213                                   0.06_wp, 0.06_wp, 0.06_wp,            & !  1
214                                   0.09_wp, 0.28_wp, 0.19_wp,            & !  2
215                                   0.11_wp, 0.33_wp, 0.23_wp,            & !  3
216                                   0.11_wp, 0.33_wp, 0.23_wp,            & !  4
217                                   0.14_wp, 0.34_wp, 0.25_wp,            & !  5
218                                   0.06_wp, 0.22_wp, 0.14_wp,            & !  6
219                                   0.06_wp, 0.27_wp, 0.17_wp,            & !  7
220                                   0.06_wp, 0.31_wp, 0.19_wp,            & !  8
221                                   0.06_wp, 0.22_wp, 0.14_wp,            & !  9
222                                   0.06_wp, 0.28_wp, 0.18_wp,            & ! 10
223                                   0.35_wp, 0.51_wp, 0.43_wp,            & ! 11
224                                   0.24_wp, 0.40_wp, 0.32_wp,            & ! 12
225                                   0.10_wp, 0.27_wp, 0.19_wp,            & ! 13
226                                   0.90_wp, 0.65_wp, 0.77_wp,            & ! 14
[1587]227                                   0.90_wp, 0.65_wp, 0.77_wp,            & ! 15
228                                   0.95_wp, 0.70_wp, 0.82_wp             & ! 16
229                                 /), (/ 3, 16 /) )
[1496]230
[1585]231    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET :: &
[1691]232                        rad_lw_cs_hr,                  & !< longwave clear sky radiation heating rate (K/s)
233                        rad_lw_cs_hr_av,               & !< average of rad_lw_cs_hr
234                        rad_lw_hr,                     & !< longwave radiation heating rate (K/s)
235                        rad_lw_hr_av,                  & !< average of rad_sw_hr
236                        rad_lw_in,                     & !< incoming longwave radiation (W/m2)
237                        rad_lw_in_av,                  & !< average of rad_lw_in
238                        rad_lw_out,                    & !< outgoing longwave radiation (W/m2)
239                        rad_lw_out_av,                 & !< average of rad_lw_out
240                        rad_sw_cs_hr,                  & !< shortwave clear sky radiation heating rate (K/s)
241                        rad_sw_cs_hr_av,               & !< average of rad_sw_cs_hr
242                        rad_sw_hr,                     & !< shortwave radiation heating rate (K/s)
243                        rad_sw_hr_av,                  & !< average of rad_sw_hr
[1682]244                        rad_sw_in,                     & !< incoming shortwave radiation (W/m2)
245                        rad_sw_in_av,                  & !< average of rad_sw_in
246                        rad_sw_out,                    & !< outgoing shortwave radiation (W/m2)
[1691]247                        rad_sw_out_av                    !< average of rad_sw_out
[1585]248
[1691]249
[1585]250!
251!-- Variables and parameters used in RRTMG only
252#if defined ( __rrtmg )
[1682]253    CHARACTER(LEN=12) :: rrtm_input_file = "RAD_SND_DATA" !< name of the NetCDF input file (sounding data)
[1585]254
255
256!
257!-- Flag parameters for RRTMGS (should not be changed)
[1682]258    INTEGER(iwp), PARAMETER :: rrtm_inflglw  = 2, & !< flag for lw cloud optical properties (0,1,2)
259                               rrtm_iceflglw = 0, & !< flag for lw ice particle specifications (0,1,2,3)
260                               rrtm_liqflglw = 1, & !< flag for lw liquid droplet specifications
261                               rrtm_inflgsw  = 2, & !< flag for sw cloud optical properties (0,1,2)
262                               rrtm_iceflgsw = 0, & !< flag for sw ice particle specifications (0,1,2,3)
263                               rrtm_liqflgsw = 1    !< flag for sw liquid droplet specifications
[1585]264
265!
266!-- The following variables should be only changed with care, as this will
267!-- require further setting of some variables, which is currently not
268!-- implemented (aerosols, ice phase).
[1682]269    INTEGER(iwp) :: nzt_rad,           & !< upper vertical limit for radiation calculations
270                    rrtm_icld = 0,     & !< cloud flag (0: clear sky column, 1: cloudy column)
271                    rrtm_iaer = 0,     & !< aerosol option flag (0: no aerosol layers, for lw only: 6 (requires setting of rrtm_sw_ecaer), 10: one or more aerosol layers (not implemented)
[1691]272                    rrtm_idrv = 1        !< longwave upward flux calculation option (0,1)
[1585]273
[1682]274    LOGICAL :: snd_exists = .FALSE.      !< flag parameter to check whether a user-defined input files exists
[1585]275
[1691]276    REAL(wp), PARAMETER :: mol_mass_air_d_wv = 1.607793_wp !< molecular weight dry air / water vapor
[1585]277
[1682]278    REAL(wp), DIMENSION(:), ALLOCATABLE :: hyp_snd,     & !< hypostatic pressure from sounding data (hPa)
279                                           q_snd,       & !< specific humidity from sounding data (kg/kg) - dummy at the moment
280                                           rrtm_tsfc,   & !< dummy array for storing surface temperature
281                                           t_snd          !< actual temperature from sounding data (hPa)
[1585]282
[1691]283    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: aldif,          & !< longwave diffuse albedo solar angle of 60°
284                                             aldir,          & !< longwave direct albedo solar angle of 60°
285                                             asdif,          & !< shortwave diffuse albedo solar angle of 60°
286                                             asdir,          & !< shortwave direct albedo solar angle of 60°
287                                             rrtm_ccl4vmr,   & !< CCL4 volume mixing ratio (g/mol)
288                                             rrtm_cfc11vmr,  & !< CFC11 volume mixing ratio (g/mol)
289                                             rrtm_cfc12vmr,  & !< CFC12 volume mixing ratio (g/mol)
290                                             rrtm_cfc22vmr,  & !< CFC22 volume mixing ratio (g/mol)
291                                             rrtm_ch4vmr,    & !< CH4 volume mixing ratio
292                                             rrtm_cicewp,    & !< in-cloud ice water path (g/m²)
293                                             rrtm_cldfr,     & !< cloud fraction (0,1)
294                                             rrtm_cliqwp,    & !< in-cloud liquid water path (g/m²)
295                                             rrtm_co2vmr,    & !< CO2 volume mixing ratio (g/mol)
296                                             rrtm_emis,      & !< surface emissivity (0-1)   
297                                             rrtm_h2ovmr,    & !< H2O volume mixing ratio
298                                             rrtm_n2ovmr,    & !< N2O volume mixing ratio
299                                             rrtm_o2vmr,     & !< O2 volume mixing ratio
300                                             rrtm_o3vmr,     & !< O3 volume mixing ratio
301                                             rrtm_play,      & !< pressure layers (hPa, zu-grid)
302                                             rrtm_plev,      & !< pressure layers (hPa, zw-grid)
303                                             rrtm_reice,     & !< cloud ice effective radius (microns)
304                                             rrtm_reliq,     & !< cloud water drop effective radius (microns)
305                                             rrtm_tlay,      & !< actual temperature (K, zu-grid)
306                                             rrtm_tlev,      & !< actual temperature (K, zw-grid)
307                                             rrtm_lwdflx,    & !< RRTM output of incoming longwave radiation flux (W/m2)
308                                             rrtm_lwdflxc,   & !< RRTM output of outgoing clear sky longwave radiation flux (W/m2)
309                                             rrtm_lwuflx,    & !< RRTM output of outgoing longwave radiation flux (W/m2)
310                                             rrtm_lwuflxc,   & !< RRTM output of incoming clear sky longwave radiation flux (W/m2)
311                                             rrtm_lwuflx_dt, & !< RRTM output of incoming clear sky longwave radiation flux (W/m2)
312                                             rrtm_lwuflxc_dt,& !< RRTM output of outgoing clear sky longwave radiation flux (W/m2)
313                                             rrtm_lwhr,      & !< RRTM output of longwave radiation heating rate (K/d)
314                                             rrtm_lwhrc,     & !< RRTM output of incoming longwave clear sky radiation heating rate (K/d)
315                                             rrtm_swdflx,    & !< RRTM output of incoming shortwave radiation flux (W/m2)
316                                             rrtm_swdflxc,   & !< RRTM output of outgoing clear sky shortwave radiation flux (W/m2)
317                                             rrtm_swuflx,    & !< RRTM output of outgoing shortwave radiation flux (W/m2)
318                                             rrtm_swuflxc,   & !< RRTM output of incoming clear sky shortwave radiation flux (W/m2)
319                                             rrtm_swhr,      & !< RRTM output of shortwave radiation heating rate (K/d)
320                                             rrtm_swhrc        !< RRTM output of incoming shortwave clear sky radiation heating rate (K/d)
[1585]321
322!
323!-- Definition of arrays that are currently not used for calling RRTMG (due to setting of flag parameters)
[1682]324    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rad_lw_cs_in,   & !< incoming clear sky longwave radiation (W/m2) (not used)
325                                                rad_lw_cs_out,  & !< outgoing clear sky longwave radiation (W/m2) (not used)
326                                                rad_sw_cs_in,   & !< incoming clear sky shortwave radiation (W/m2) (not used)
327                                                rad_sw_cs_out,  & !< outgoing clear sky shortwave radiation (W/m2) (not used)
328                                                rrtm_aldif,     & !< surface albedo for longwave diffuse radiation
329                                                rrtm_aldir,     & !< surface albedo for longwave direct radiation
330                                                rrtm_asdif,     & !< surface albedo for shortwave diffuse radiation
331                                                rrtm_asdir,     & !< surface albedo for shortwave direct radiation
332                                                rrtm_lw_tauaer, & !< lw aerosol optical depth
333                                                rrtm_lw_taucld, & !< lw in-cloud optical depth
334                                                rrtm_sw_taucld, & !< sw in-cloud optical depth
335                                                rrtm_sw_ssacld, & !< sw in-cloud single scattering albedo
336                                                rrtm_sw_asmcld, & !< sw in-cloud asymmetry parameter
337                                                rrtm_sw_fsfcld, & !< sw in-cloud forward scattering fraction
338                                                rrtm_sw_tauaer, & !< sw aerosol optical depth
339                                                rrtm_sw_ssaaer, & !< sw aerosol single scattering albedo
340                                                rrtm_sw_asmaer, & !< sw aerosol asymmetry parameter
341                                                rrtm_sw_ecaer     !< sw aerosol optical detph at 0.55 microns (rrtm_iaer = 6 only)
[1691]342
[1585]343#endif
344
[1496]345    INTERFACE init_radiation
346       MODULE PROCEDURE init_radiation
347    END INTERFACE init_radiation
348
[1551]349    INTERFACE radiation_clearsky
350       MODULE PROCEDURE radiation_clearsky
351    END INTERFACE radiation_clearsky
[1496]352
[1585]353    INTERFACE radiation_rrtmg
354       MODULE PROCEDURE radiation_rrtmg
355    END INTERFACE radiation_rrtmg
[1551]356
[1585]357    INTERFACE radiation_tendency
358       MODULE PROCEDURE radiation_tendency
359       MODULE PROCEDURE radiation_tendency_ij
360    END INTERFACE radiation_tendency
[1551]361
[1496]362    SAVE
363
364    PRIVATE
365
[1585]366    PUBLIC albedo, albedo_type, albedo_type_name, albedo_lw_dif, albedo_lw_dir,&
367           albedo_sw_dif, albedo_sw_dir, constant_albedo, day_init, dots_rad,  &
[1691]368           dt_radiation, emissivity, force_radiation_call, init_radiation,     &
369           lambda, lw_radiation, net_radiation, rad_net, rad_net_av, radiation,&
370           radiation_clearsky, radiation_rrtmg, radiation_scheme,              &
371           radiation_tendency, rad_lw_in, rad_lw_in_av, rad_lw_out,            &
[1709]372           rad_lw_out_av, rad_lw_out_change_0, rad_lw_cs_hr, rad_lw_cs_hr_av,  &
373           rad_lw_hr, rad_lw_hr_av, rad_sw_in, rad_sw_in_av, rad_sw_out,       &
374           rad_sw_out_av, rad_sw_cs_hr, rad_sw_cs_hr_av, rad_sw_hr,            &
375           rad_sw_hr_av, sigma_sb, skip_time_do_radiation, sw_radiation,       &
[1757]376           time_radiation, time_utc_init, unscheduled_radiation_calls
[1496]377
[1691]378
[1585]379#if defined ( __rrtmg )
[1709]380    PUBLIC rrtm_aldif, rrtm_aldir, rrtm_asdif, rrtm_asdir, rrtm_idrv
[1585]381#endif
[1496]382
383 CONTAINS
384
385!------------------------------------------------------------------------------!
386! Description:
387! ------------
[1682]388!> Initialization of the radiation model
[1496]389!------------------------------------------------------------------------------!
390    SUBROUTINE init_radiation
391   
392       IMPLICIT NONE
393
[1585]394!
395!--    Allocate array for storing the surface net radiation
396       IF ( .NOT. ALLOCATED ( rad_net ) )  THEN
397          ALLOCATE ( rad_net(nysg:nyng,nxlg:nxrg) )
398          rad_net = 0.0_wp
399       ENDIF
[1496]400
401!
[1709]402!--    Allocate array for storing the surface net radiation
403       IF ( .NOT. ALLOCATED ( rad_lw_out_change_0 ) )  THEN
404          ALLOCATE ( rad_lw_out_change_0(nysg:nyng,nxlg:nxrg) )
405          rad_lw_out_change_0 = 0.0_wp
406       ENDIF
407
408!
[1551]409!--    Fix net radiation in case of radiation_scheme = 'constant'
[1585]410       IF ( radiation_scheme == 'constant' )  THEN
[1551]411          rad_net = net_radiation
[1585]412          radiation = .FALSE.
[1551]413!
[1585]414!--    Calculate orbital constants
415       ELSE
[1551]416          decl_1 = SIN(23.45_wp * pi / 180.0_wp)
417          decl_2 = 2.0_wp * pi / 365.0_wp
418          decl_3 = decl_2 * 81.0_wp
[1585]419          lat    = phi * pi / 180.0_wp
420          lon    = lambda * pi / 180.0_wp
421       ENDIF
422
423
424       IF ( radiation_scheme == 'clear-sky' )  THEN
425
426          ALLOCATE ( alpha(nysg:nyng,nxlg:nxrg) )
427
428          IF ( .NOT. ALLOCATED ( rad_sw_in ) )  THEN
429             ALLOCATE ( rad_sw_in(0:0,nysg:nyng,nxlg:nxrg) )
430          ENDIF
431          IF ( .NOT. ALLOCATED ( rad_sw_out ) )  THEN
432             ALLOCATE ( rad_sw_out(0:0,nysg:nyng,nxlg:nxrg) )
433          ENDIF
434
435          IF ( .NOT. ALLOCATED ( rad_sw_in_av ) )  THEN
436             ALLOCATE ( rad_sw_in_av(0:0,nysg:nyng,nxlg:nxrg) )
437          ENDIF
438          IF ( .NOT. ALLOCATED ( rad_sw_out_av ) )  THEN
439             ALLOCATE ( rad_sw_out_av(0:0,nysg:nyng,nxlg:nxrg) )
440          ENDIF
441
442          IF ( .NOT. ALLOCATED ( rad_lw_in ) )  THEN
443             ALLOCATE ( rad_lw_in(0:0,nysg:nyng,nxlg:nxrg) )
444          ENDIF
445          IF ( .NOT. ALLOCATED ( rad_lw_out ) )  THEN
446             ALLOCATE ( rad_lw_out(0:0,nysg:nyng,nxlg:nxrg) )
447          ENDIF
448
449          IF ( .NOT. ALLOCATED ( rad_lw_in_av ) )  THEN
450             ALLOCATE ( rad_lw_in_av(0:0,nysg:nyng,nxlg:nxrg) )
451          ENDIF
452          IF ( .NOT. ALLOCATED ( rad_lw_out_av ) )  THEN
453             ALLOCATE ( rad_lw_out_av(0:0,nysg:nyng,nxlg:nxrg) )
454          ENDIF
455
456          rad_sw_in  = 0.0_wp
457          rad_sw_out = 0.0_wp
458          rad_lw_in  = 0.0_wp
459          rad_lw_out = 0.0_wp
460
[1496]461!
[1585]462!--       Overwrite albedo if manually set in parameter file
463          IF ( albedo_type /= 0 .AND. albedo == 9999999.9_wp )  THEN
464             albedo = albedo_pars(2,albedo_type)
465          ENDIF
466   
467          alpha = albedo
468 
469!
470!--    Initialization actions for RRTMG
471       ELSEIF ( radiation_scheme == 'rrtmg' )  THEN
472#if defined ( __rrtmg )
473!
474!--       Allocate albedos
475          ALLOCATE ( rrtm_aldif(0:0,nysg:nyng,nxlg:nxrg) )
476          ALLOCATE ( rrtm_aldir(0:0,nysg:nyng,nxlg:nxrg) )
477          ALLOCATE ( rrtm_asdif(0:0,nysg:nyng,nxlg:nxrg) )
478          ALLOCATE ( rrtm_asdir(0:0,nysg:nyng,nxlg:nxrg) )
479          ALLOCATE ( aldif(nysg:nyng,nxlg:nxrg) )
480          ALLOCATE ( aldir(nysg:nyng,nxlg:nxrg) )
481          ALLOCATE ( asdif(nysg:nyng,nxlg:nxrg) )
482          ALLOCATE ( asdir(nysg:nyng,nxlg:nxrg) )
483
484          IF ( albedo_type /= 0 )  THEN
485             IF ( albedo_lw_dif == 9999999.9_wp )  THEN
486                albedo_lw_dif = albedo_pars(0,albedo_type)
487                albedo_lw_dir = albedo_lw_dif
488             ENDIF
489             IF ( albedo_sw_dif == 9999999.9_wp )  THEN
490                albedo_sw_dif = albedo_pars(1,albedo_type)
491                albedo_sw_dir = albedo_sw_dif
492             ENDIF
493          ENDIF
494
495          aldif(:,:) = albedo_lw_dif
496          aldir(:,:) = albedo_lw_dir
497          asdif(:,:) = albedo_sw_dif
498          asdir(:,:) = albedo_sw_dir
499!
500!--       Calculate initial values of current (cosine of) the zenith angle and
501!--       whether the sun is up
502          CALL calc_zenith     
503!
504!--       Calculate initial surface albedo
505          IF ( .NOT. constant_albedo )  THEN
506             CALL calc_albedo
507          ELSE
508             rrtm_aldif(0,:,:) = aldif(:,:)
509             rrtm_aldir(0,:,:) = aldir(:,:)
510             rrtm_asdif(0,:,:) = asdif(:,:) 
511             rrtm_asdir(0,:,:) = asdir(:,:)   
512          ENDIF
513
514!
515!--       Allocate surface emissivity
516          ALLOCATE ( rrtm_emis(0:0,1:nbndlw+1) )
517          rrtm_emis = emissivity
518
519!
520!--       Allocate 3d arrays of radiative fluxes and heating rates
521          IF ( .NOT. ALLOCATED ( rad_sw_in ) )  THEN
522             ALLOCATE ( rad_sw_in(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
523             rad_sw_in = 0.0_wp
524          ENDIF
525
526          IF ( .NOT. ALLOCATED ( rad_sw_in_av ) )  THEN
527             ALLOCATE ( rad_sw_in_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
528          ENDIF
529
530          IF ( .NOT. ALLOCATED ( rad_sw_out ) )  THEN
531             ALLOCATE ( rad_sw_out(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1691]532             rad_sw_out = 0.0_wp
[1585]533          ENDIF
534
535          IF ( .NOT. ALLOCATED ( rad_sw_out_av ) )  THEN
536             ALLOCATE ( rad_sw_out_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
537          ENDIF
538
[1691]539          IF ( .NOT. ALLOCATED ( rad_sw_hr ) )  THEN
540             ALLOCATE ( rad_sw_hr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
541             rad_sw_hr = 0.0_wp
542          ENDIF
[1585]543
[1691]544          IF ( .NOT. ALLOCATED ( rad_sw_hr_av ) )  THEN
545             ALLOCATE ( rad_sw_hr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
546             rad_sw_hr_av = 0.0_wp
547          ENDIF
548
549          IF ( .NOT. ALLOCATED ( rad_sw_cs_hr ) )  THEN
550             ALLOCATE ( rad_sw_cs_hr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
551             rad_sw_cs_hr = 0.0_wp
552          ENDIF
553
554          IF ( .NOT. ALLOCATED ( rad_sw_cs_hr_av ) )  THEN
555             ALLOCATE ( rad_sw_cs_hr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
556             rad_sw_cs_hr_av = 0.0_wp
557          ENDIF
558
[1585]559          IF ( .NOT. ALLOCATED ( rad_lw_in ) )  THEN
560             ALLOCATE ( rad_lw_in(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
561             rad_lw_in     = 0.0_wp
562          ENDIF
563
564          IF ( .NOT. ALLOCATED ( rad_lw_in_av ) )  THEN
565             ALLOCATE ( rad_lw_in_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
566          ENDIF
567
568          IF ( .NOT. ALLOCATED ( rad_lw_out ) )  THEN
569             ALLOCATE ( rad_lw_out(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
570            rad_lw_out    = 0.0_wp
571          ENDIF
572
573          IF ( .NOT. ALLOCATED ( rad_lw_out_av ) )  THEN
574             ALLOCATE ( rad_lw_out_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
575          ENDIF
576
[1691]577          IF ( .NOT. ALLOCATED ( rad_lw_hr ) )  THEN
578             ALLOCATE ( rad_lw_hr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
579             rad_lw_hr = 0.0_wp
580          ENDIF
581
582          IF ( .NOT. ALLOCATED ( rad_lw_hr_av ) )  THEN
583             ALLOCATE ( rad_lw_hr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
584             rad_lw_hr_av = 0.0_wp
585          ENDIF
586
587          IF ( .NOT. ALLOCATED ( rad_lw_cs_hr ) )  THEN
588             ALLOCATE ( rad_lw_cs_hr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
589             rad_lw_cs_hr = 0.0_wp
590          ENDIF
591
592          IF ( .NOT. ALLOCATED ( rad_lw_cs_hr_av ) )  THEN
593             ALLOCATE ( rad_lw_cs_hr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
594             rad_lw_cs_hr_av = 0.0_wp
595          ENDIF
596
597          ALLOCATE ( rad_sw_cs_in(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
598          ALLOCATE ( rad_sw_cs_out(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1585]599          rad_sw_cs_in  = 0.0_wp
600          rad_sw_cs_out = 0.0_wp
601
[1691]602          ALLOCATE ( rad_lw_cs_in(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
603          ALLOCATE ( rad_lw_cs_out(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1585]604          rad_lw_cs_in  = 0.0_wp
605          rad_lw_cs_out = 0.0_wp
606
607!
608!--       Allocate dummy array for storing surface temperature
609          ALLOCATE ( rrtm_tsfc(1) )
610
611!
612!--       Initialize RRTMG
613          IF ( lw_radiation )  CALL rrtmg_lw_ini ( cp )
614          IF ( sw_radiation )  CALL rrtmg_sw_ini ( cp )
615
616!
617!--       Set input files for RRTMG
618          INQUIRE(FILE="RAD_SND_DATA", EXIST=snd_exists) 
619          IF ( .NOT. snd_exists )  THEN
620             rrtm_input_file = "rrtmg_lw.nc"
621          ENDIF
622
623!
624!--       Read vertical layers for RRTMG from sounding data
625!--       The routine provides nzt_rad, hyp_snd(1:nzt_rad),
626!--       t_snd(nzt+2:nzt_rad), rrtm_play(1:nzt_rad), rrtm_plev(1_nzt_rad+1),
627!--       rrtm_tlay(nzt+2:nzt_rad), rrtm_tlev(nzt+2:nzt_rad+1)
628          CALL read_sounding_data
629
630!
631!--       Read trace gas profiles from file. This routine provides
632!--       the rrtm_ arrays (1:nzt_rad+1)
633          CALL read_trace_gas_data
634#endif
[1551]635       ENDIF
[1585]636
[1551]637!
[1585]638!--    Perform user actions if required
639       CALL user_init_radiation
640
641
642!
[1551]643!--    Add timeseries for radiation model
[1585]644       dots_rad = dots_num + 1
[1691]645       dots_num = dots_num + 5
[1496]646
[1701]647       dots_label(dots_rad) = "rad_net"
648       dots_label(dots_rad+1) = "rad_lw_in"
649       dots_label(dots_rad+2) = "rad_lw_out"
650       dots_label(dots_rad+3) = "rad_sw_in"
651       dots_label(dots_rad+4) = "rad_sw_out"
[1691]652       dots_unit(dots_rad:dots_rad+4) = "W/m2"
653
[1585]654!
655!--    Output of albedos is only required for RRTMG
656       IF ( radiation_scheme == 'rrtmg' )  THEN
657          dots_num  = dots_num + 4
[1691]658          dots_label(dots_rad+5) = "rrtm_aldif"
659          dots_label(dots_rad+6) = "rrtm_aldir"
660          dots_label(dots_rad+7) = "rrtm_asdif"
661          dots_label(dots_rad+8) = "rrtm_asdir"
662          dots_unit(dots_num+5:dots_num+8) = ""
663
[1585]664       ENDIF
[1551]665
[1585]666!
667!--    Calculate radiative fluxes at model start
668       IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
669          IF ( radiation_scheme == 'clear-sky' )  THEN
[1709]670             CALL radiation_clearsky
[1585]671          ELSEIF ( radiation_scheme == 'rrtmg' )  THEN
672             CALL radiation_rrtmg
673          ENDIF
674       ENDIF
675
[1496]676       RETURN
677
678    END SUBROUTINE init_radiation
679
680
681!------------------------------------------------------------------------------!
682! Description:
683! ------------
[1682]684!> A simple clear sky radiation model
[1496]685!------------------------------------------------------------------------------!
[1551]686    SUBROUTINE radiation_clearsky
[1496]687
[1585]688       USE indices,                                                            &
689           ONLY:  nbgp
690
[1496]691       IMPLICIT NONE
692
[1691]693       INTEGER(iwp) :: i, j, k   !< loop indices
694       REAL(wp)     :: exn,   &  !< Exner functions at surface
[1709]695                       exn1,  &  !< Exner functions at first grid level
696                       pt1       !< potential temperature at first grid level
[1585]697
[1496]698!
[1585]699!--    Calculate current zenith angle
700       CALL calc_zenith
701
702!
703!--    Calculate sky transmissivity
704       sky_trans = 0.6_wp + 0.2_wp * zenith(0)
705
706!
707!--    Calculate value of the Exner function
708       exn = (surface_pressure / 1000.0_wp )**0.286_wp
709!
710!--    Calculate radiation fluxes and net radiation (rad_net) for each grid
711!--    point
[1709]712       DO i = nxlg, nxrg
713          DO j = nysg, nyng
[1585]714             k = nzb_s_inner(j,i)
[1691]715
[1709]716             exn1 = (hyp(k+1) / 100000.0_wp )**0.286_wp
[1691]717
[1585]718             rad_sw_in(0,j,i)  = solar_constant * sky_trans * zenith(0)
719             rad_sw_out(0,j,i) = alpha(j,i) * rad_sw_in(0,j,i)
[1691]720             rad_lw_out(0,j,i) = emissivity * sigma_sb * (pt(k,j,i) * exn)**4
[1585]721
[1691]722             IF ( cloud_physics )  THEN
[1709]723                pt1 = pt(k+1,j,i) + l_d_cp / exn1 * ql(k+1,j,i)
724                rad_lw_in(0,j,i)  = 0.8_wp * sigma_sb * (pt1 * exn1)**4
[1691]725             ELSE
[1709]726                rad_lw_in(0,j,i)  = 0.8_wp * sigma_sb * (pt(k+1,j,i) * exn1)**4
[1691]727             ENDIF
728
729             rad_net(j,i) = rad_sw_in(0,j,i) - rad_sw_out(0,j,i)               &
730                            + rad_lw_in(0,j,i) - rad_lw_out(0,j,i)
731
[1585]732          ENDDO
733       ENDDO
734
735    END SUBROUTINE radiation_clearsky
736
737
738!------------------------------------------------------------------------------!
739! Description:
740! ------------
[1682]741!> Implementation of the RRTMG radiation_scheme
[1585]742!------------------------------------------------------------------------------!
743    SUBROUTINE radiation_rrtmg
744
745       USE indices,                                                            &
746           ONLY:  nbgp
747
748       USE particle_attributes,                                                &
749           ONLY:  grid_particles, number_of_particles, particles,              &
750                  particle_advection_start, prt_count
751
752       IMPLICIT NONE
753
754#if defined ( __rrtmg )
755
[1691]756       INTEGER(iwp) :: i, j, k, n !< loop indices
[1585]757
[1691]758       REAL(wp)     ::  s_r2, &   !< weighted sum over all droplets with r^2
759                        s_r3      !< weighted sum over all droplets with r^3
[1585]760
761!
762!--    Calculate current (cosine of) zenith angle and whether the sun is up
763       CALL calc_zenith     
764!
765!--    Calculate surface albedo
766       IF ( .NOT. constant_albedo )  THEN
767          CALL calc_albedo
768       ENDIF
769
770!
771!--    Prepare input data for RRTMG
772
773!
774!--    In case of large scale forcing with surface data, calculate new pressure
775!--    profile. nzt_rad might be modified by these calls and all required arrays
776!--    will then be re-allocated
[1691]777       IF ( large_scale_forcing  .AND.  lsf_surf )  THEN
[1585]778          CALL read_sounding_data
779          CALL read_trace_gas_data
780       ENDIF
781!
782!--    Loop over all grid points
783       DO i = nxl, nxr
784          DO j = nys, nyn
785
786!
787!--          Prepare profiles of temperature and H2O volume mixing ratio
[1691]788             rrtm_tlev(0,nzb+1) = pt(nzb,j,i) * ( surface_pressure             &
789                                                  / 1000.0_wp )**0.286_wp
[1585]790
791             DO k = nzb+1, nzt+1
792                rrtm_tlay(0,k) = pt(k,j,i) * ( (hyp(k) ) / 100000.0_wp         &
[1691]793                                 )**0.286_wp + l_d_cp * ql(k,j,i)
794                rrtm_h2ovmr(0,k) = mol_mass_air_d_wv * (q(k,j,i) - ql(k,j,i))
[1585]795
796             ENDDO
797
798!
799!--          Avoid temperature/humidity jumps at the top of the LES domain by
800!--          linear interpolation from nzt+2 to nzt+7
801             DO k = nzt+2, nzt+7
802                rrtm_tlay(0,k) = rrtm_tlay(0,nzt+1)                            &
803                              + ( rrtm_tlay(0,nzt+8) - rrtm_tlay(0,nzt+1) )    &
804                              / ( rrtm_play(0,nzt+8) - rrtm_play(0,nzt+1) )    &
805                              * ( rrtm_play(0,k) - rrtm_play(0,nzt+1) )
806
807                rrtm_h2ovmr(0,k) = rrtm_h2ovmr(0,nzt+1)                        &
808                              + ( rrtm_h2ovmr(0,nzt+8) - rrtm_h2ovmr(0,nzt+1) )&
809                              / ( rrtm_play(0,nzt+8)   - rrtm_play(0,nzt+1)   )&
810                              * ( rrtm_play(0,k) - rrtm_play(0,nzt+1) )
811
812             ENDDO
813
814!--          Linear interpolate to zw grid
815             DO k = nzb+2, nzt+8
816                rrtm_tlev(0,k)   = rrtm_tlay(0,k-1) + (rrtm_tlay(0,k) -        &
817                                   rrtm_tlay(0,k-1))                           &
818                                   / ( rrtm_play(0,k) - rrtm_play(0,k-1) )     &
819                                   * ( rrtm_plev(0,k) - rrtm_play(0,k-1) )
820             ENDDO
821
822
823!
824!--          Calculate liquid water path and cloud fraction for each column.
825!--          Note that LWP is required in g/m² instead of kg/kg m.
826             rrtm_cldfr  = 0.0_wp
827             rrtm_reliq  = 0.0_wp
828             rrtm_cliqwp = 0.0_wp
[1691]829             rrtm_icld   = 0
[1585]830
831             DO k = nzb+1, nzt+1
[1691]832                rrtm_cliqwp(0,k) =  ql(k,j,i) * 1000.0_wp *                    &
833                                    (rrtm_plev(0,k) - rrtm_plev(0,k+1))        &
834                                    * 100.0_wp / g 
[1585]835
[1691]836                IF ( rrtm_cliqwp(0,k) > 0.0_wp )  THEN
[1585]837                   rrtm_cldfr(0,k) = 1.0_wp
[1691]838                   IF ( rrtm_icld == 0 )  rrtm_icld = 1
[1585]839
840!
841!--                Calculate cloud droplet effective radius
842                   IF ( cloud_physics )  THEN
[1691]843                      rrtm_reliq(0,k) = 1.0E6_wp * ( 3.0_wp * ql(k,j,i)        &
844                                        * rho_surface                          &
845                                        / ( 4.0_wp * pi * nc_const * rho_l )   &
846                                        )**0.33333333333333_wp                 &
847                                        * EXP( LOG( sigma_gc )**2 )
[1585]848
849                   ELSEIF ( cloud_droplets )  THEN
850                      number_of_particles = prt_count(k,j,i)
851
852                      IF (number_of_particles <= 0)  CYCLE
853                      particles => grid_particles(k,j,i)%particles(1:number_of_particles)
854                      s_r2 = 0.0_wp
855                      s_r3 = 0.0_wp
856
857                      DO  n = 1, number_of_particles
858                         IF ( particles(n)%particle_mask )  THEN
859                            s_r2 = s_r2 + particles(n)%radius**2 * &
860                                   particles(n)%weight_factor
861                            s_r3 = s_r3 + particles(n)%radius**3 * &
862                                   particles(n)%weight_factor
863                         ENDIF
864                      ENDDO
865
866                      IF ( s_r2 > 0.0_wp )  rrtm_reliq(0,k) = s_r3 / s_r2
867
868                   ENDIF
869
870!
871!--                Limit effective radius
[1691]872                   IF ( rrtm_reliq(0,k) > 0.0_wp )  THEN
[1585]873                      rrtm_reliq(0,k) = MAX(rrtm_reliq(0,k),2.5_wp)
874                      rrtm_reliq(0,k) = MIN(rrtm_reliq(0,k),60.0_wp)
875                  ENDIF
876                ENDIF
877             ENDDO
878
879!
880!--          Set surface temperature
881             rrtm_tsfc = pt(nzb,j,i) * (surface_pressure / 1000.0_wp )**0.286_wp
882
883             IF ( lw_radiation )  THEN
884               CALL rrtmg_lw( 1, nzt_rad      , rrtm_icld    , rrtm_idrv      ,&
885               rrtm_play       , rrtm_plev    , rrtm_tlay    , rrtm_tlev      ,&
886               rrtm_tsfc       , rrtm_h2ovmr  , rrtm_o3vmr   , rrtm_co2vmr    ,&
887               rrtm_ch4vmr     , rrtm_n2ovmr  , rrtm_o2vmr   , rrtm_cfc11vmr  ,&
888               rrtm_cfc12vmr   , rrtm_cfc22vmr, rrtm_ccl4vmr , rrtm_emis      ,&
889               rrtm_inflglw    , rrtm_iceflglw, rrtm_liqflglw, rrtm_cldfr     ,&
890               rrtm_lw_taucld  , rrtm_cicewp  , rrtm_cliqwp  , rrtm_reice     ,& 
891               rrtm_reliq      , rrtm_lw_tauaer,                               &
892               rrtm_lwuflx     , rrtm_lwdflx  , rrtm_lwhr  ,                   &
[1691]893               rrtm_lwuflxc    , rrtm_lwdflxc , rrtm_lwhrc ,                   &
894               rrtm_lwuflx_dt  ,  rrtm_lwuflxc_dt )
[1585]895
[1691]896!
897!--             Save fluxes
[1585]898                DO k = nzb, nzt+1
899                   rad_lw_in(k,j,i)  = rrtm_lwdflx(0,k)
900                   rad_lw_out(k,j,i) = rrtm_lwuflx(0,k)
901                ENDDO
902
[1691]903!
904!--             Save heating rates (convert from K/d to K/h)
905                DO k = nzb+1, nzt+1
906                   rad_lw_hr(k,j,i)     = rrtm_lwhr(0,k)  * d_hours_day
907                   rad_lw_cs_hr(k,j,i)  = rrtm_lwhrc(0,k) * d_hours_day
908                ENDDO
[1585]909
[1709]910!
911!--             Save change in LW heating rate
912                rad_lw_out_change_0(j,i) = rrtm_lwuflx_dt(0,nzb)
913
[1585]914             ENDIF
915
916             IF ( sw_radiation .AND. sun_up )  THEN
917                CALL rrtmg_sw( 1, nzt_rad      , rrtm_icld  , rrtm_iaer       ,&
918               rrtm_play       , rrtm_plev    , rrtm_tlay  , rrtm_tlev        ,&
919               rrtm_tsfc       , rrtm_h2ovmr  , rrtm_o3vmr , rrtm_co2vmr      ,&
920               rrtm_ch4vmr     , rrtm_n2ovmr  , rrtm_o2vmr , rrtm_asdir(:,j,i),&
921               rrtm_asdif(:,j,i), rrtm_aldir(:,j,i), rrtm_aldif(:,j,i), zenith,&
922               0.0_wp          , day          , solar_constant,   rrtm_inflgsw,&
923               rrtm_iceflgsw   , rrtm_liqflgsw, rrtm_cldfr , rrtm_sw_taucld   ,&
924               rrtm_sw_ssacld  , rrtm_sw_asmcld, rrtm_sw_fsfcld, rrtm_cicewp  ,&
925               rrtm_cliqwp     , rrtm_reice   , rrtm_reliq , rrtm_sw_tauaer   ,&
926               rrtm_sw_ssaaer     , rrtm_sw_asmaer  , rrtm_sw_ecaer ,          &
927               rrtm_swuflx     , rrtm_swdflx  , rrtm_swhr  ,                   &
928               rrtm_swuflxc    , rrtm_swdflxc , rrtm_swhrc )
929 
[1691]930!
931!--             Save fluxes
[1585]932                DO k = nzb, nzt+1
933                   rad_sw_in(k,j,i)  = rrtm_swdflx(0,k)
934                   rad_sw_out(k,j,i) = rrtm_swuflx(0,k)
935                ENDDO
[1691]936
937!
938!--             Save heating rates (convert from K/d to K/s)
939                DO k = nzb+1, nzt+1
940                   rad_sw_hr(k,j,i)     = rrtm_swhr(0,k)  * d_hours_day
941                   rad_sw_cs_hr(k,j,i)  = rrtm_swhrc(0,k) * d_hours_day
942                ENDDO
943
[1585]944             ENDIF
945
946!
947!--          Calculate surface net radiation
948             rad_net(j,i) = rad_sw_in(nzb,j,i) - rad_sw_out(nzb,j,i)           &
949                            + rad_lw_in(nzb,j,i) - rad_lw_out(nzb,j,i)
950
951          ENDDO
952       ENDDO
953
954       CALL exchange_horiz( rad_lw_in,  nbgp )
955       CALL exchange_horiz( rad_lw_out, nbgp )
[1691]956       CALL exchange_horiz( rad_lw_hr,    nbgp )
957       CALL exchange_horiz( rad_lw_cs_hr, nbgp )
958
[1585]959       CALL exchange_horiz( rad_sw_in,  nbgp )
960       CALL exchange_horiz( rad_sw_out, nbgp ) 
[1691]961       CALL exchange_horiz( rad_sw_hr,    nbgp )
962       CALL exchange_horiz( rad_sw_cs_hr, nbgp )
963
[1585]964       CALL exchange_horiz_2d( rad_net, nbgp )
[1709]965       CALL exchange_horiz_2d( rad_lw_out_change_0, nbgp )
[1585]966#endif
967
968    END SUBROUTINE radiation_rrtmg
969
970
971!------------------------------------------------------------------------------!
972! Description:
973! ------------
[1682]974!> Calculate the cosine of the zenith angle (variable is called zenith)
[1585]975!------------------------------------------------------------------------------!
976    SUBROUTINE calc_zenith
977
978       IMPLICIT NONE
979
[1682]980       REAL(wp) ::  declination,  & !< solar declination angle
981                    hour_angle      !< solar hour angle
[1585]982!
[1496]983!--    Calculate current day and time based on the initial values and simulation
984!--    time
[1585]985       day = day_init + INT(FLOOR( (time_utc_init + time_since_reference_point)    &
986                               / 86400.0_wp ), KIND=iwp)
[1496]987       time_utc = MOD((time_utc_init + time_since_reference_point), 86400.0_wp)
988
989
990!
991!--    Calculate solar declination and hour angle   
[1585]992       declination = ASIN( decl_1 * SIN(decl_2 * REAL(day, KIND=wp) - decl_3) )
[1496]993       hour_angle  = 2.0_wp * pi * (time_utc / 86400.0_wp) + lon - pi
994
995!
996!--    Calculate zenith angle
[1585]997       zenith(0) = SIN(lat) * SIN(declination) + COS(lat) * COS(declination)      &
[1496]998                                            * COS(hour_angle)
[1585]999       zenith(0) = MAX(0.0_wp,zenith(0))
[1496]1000
1001!
[1585]1002!--    Check if the sun is up (otheriwse shortwave calculations can be skipped)
[1691]1003       IF ( zenith(0) > 0.0_wp )  THEN
[1585]1004          sun_up = .TRUE.
1005       ELSE
1006          sun_up = .FALSE.
1007       END IF
[1496]1008
[1585]1009    END SUBROUTINE calc_zenith
1010
[1606]1011#if defined ( __rrtmg ) && defined ( __netcdf )
[1585]1012!------------------------------------------------------------------------------!
1013! Description:
1014! ------------
[1682]1015!> Calculates surface albedo components based on Briegleb (1992) and
1016!> Briegleb et al. (1986)
[1585]1017!------------------------------------------------------------------------------!
1018    SUBROUTINE calc_albedo
1019
1020        IMPLICIT NONE
1021
1022        IF ( sun_up )  THEN
[1496]1023!
[1585]1024!--        Ocean
1025           IF ( albedo_type == 1 )  THEN
1026              rrtm_aldir(0,:,:) = 0.026_wp / ( zenith(0)**1.7_wp + 0.065_wp )  &
1027                                  + 0.15_wp * ( zenith(0) - 0.1_wp )           &
1028                                            * ( zenith(0) - 0.5_wp )           &
1029                                            * ( zenith(0) - 1.0_wp )
1030              rrtm_asdir(0,:,:) = rrtm_aldir(0,:,:)
1031!
1032!--        Snow
1033           ELSEIF ( albedo_type == 16 )  THEN
1034              IF ( zenith(0) < 0.5_wp )  THEN
1035                 rrtm_aldir(0,:,:) = 0.5_wp * (1.0_wp - aldif)                 &
1036                                     * ( 3.0_wp / (1.0_wp + 4.0_wp             &
1037                                     * zenith(0))) - 1.0_wp
1038                 rrtm_asdir(0,:,:) = 0.5_wp * (1.0_wp - asdif)                 &
1039                                     * ( 3.0_wp / (1.0_wp + 4.0_wp             &
1040                                     * zenith(0))) - 1.0_wp
[1496]1041
[1585]1042                 rrtm_aldir(0,:,:) = MIN(0.98_wp, rrtm_aldir(0,:,:))
1043                 rrtm_asdir(0,:,:) = MIN(0.98_wp, rrtm_asdir(0,:,:))
1044              ELSE
1045                 rrtm_aldir(0,:,:) = aldif
1046                 rrtm_asdir(0,:,:) = asdif
1047              ENDIF
[1496]1048!
[1585]1049!--        Sea ice
1050           ELSEIF ( albedo_type == 15 )  THEN
1051                 rrtm_aldir(0,:,:) = aldif
1052                 rrtm_asdir(0,:,:) = asdif
1053!
1054!--        Land surfaces
1055           ELSE
1056              SELECT CASE ( albedo_type )
[1496]1057
[1585]1058!
1059!--              Surface types with strong zenith dependence
1060                 CASE ( 1, 2, 3, 4, 11, 12, 13 )
1061                    rrtm_aldir(0,:,:) = aldif * 1.4_wp /                       &
1062                                        (1.0_wp + 0.8_wp * zenith(0))
1063                    rrtm_asdir(0,:,:) = asdif * 1.4_wp /                       &
1064                                        (1.0_wp + 0.8_wp * zenith(0))
1065!
1066!--              Surface types with weak zenith dependence
1067                 CASE ( 5, 6, 7, 8, 9, 10, 14 )
1068                    rrtm_aldir(0,:,:) = aldif * 1.1_wp /                       &
1069                                        (1.0_wp + 0.2_wp * zenith(0))
1070                    rrtm_asdir(0,:,:) = asdif * 1.1_wp /                       &
1071                                        (1.0_wp + 0.2_wp * zenith(0))
[1496]1072
[1585]1073                 CASE DEFAULT
1074
1075              END SELECT
1076           ENDIF
1077!
1078!--        Diffusive albedo is taken from Table 2
1079           rrtm_aldif(0,:,:) = aldif
1080           rrtm_asdif(0,:,:) = asdif
1081
1082        ELSE
1083
1084           rrtm_aldir(0,:,:) = 0.0_wp
1085           rrtm_asdir(0,:,:) = 0.0_wp
1086           rrtm_aldif(0,:,:) = 0.0_wp
1087           rrtm_asdif(0,:,:) = 0.0_wp
1088        ENDIF
1089    END SUBROUTINE calc_albedo
1090
1091!------------------------------------------------------------------------------!
1092! Description:
1093! ------------
[1682]1094!> Read sounding data (pressure and temperature) from RADIATION_DATA.
[1585]1095!------------------------------------------------------------------------------!
1096    SUBROUTINE read_sounding_data
1097
1098       USE netcdf_control
1099
1100       IMPLICIT NONE
1101
[1691]1102       INTEGER(iwp) :: id,           & !< NetCDF id of input file
1103                       id_dim_zrad,  & !< pressure level id in the NetCDF file
1104                       id_var,       & !< NetCDF variable id
1105                       k,            & !< loop index
1106                       nz_snd,       & !< number of vertical levels in the sounding data
1107                       nz_snd_start, & !< start vertical index for sounding data to be used
1108                       nz_snd_end      !< end vertical index for souding data to be used
[1585]1109
[1691]1110       REAL(wp) :: t_surface           !< actual surface temperature
[1585]1111
[1691]1112       REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp_snd_tmp, & !< temporary hydrostatic pressure profile (sounding)
1113                                               t_snd_tmp      !< temporary temperature profile (sounding)
[1585]1114
1115!
1116!--    In case of updates, deallocate arrays first (sufficient to check one
1117!--    array as the others are automatically allocated). This is required
1118!--    because nzt_rad might change during the update
1119       IF ( ALLOCATED ( hyp_snd ) )  THEN
1120          DEALLOCATE( hyp_snd )
1121          DEALLOCATE( t_snd )
1122          DEALLOCATE( q_snd  )
1123          DEALLOCATE ( rrtm_play )
1124          DEALLOCATE ( rrtm_plev )
1125          DEALLOCATE ( rrtm_tlay )
1126          DEALLOCATE ( rrtm_tlev )
[1691]1127
[1585]1128          DEALLOCATE ( rrtm_h2ovmr )
1129          DEALLOCATE ( rrtm_cicewp )
1130          DEALLOCATE ( rrtm_cldfr )
1131          DEALLOCATE ( rrtm_cliqwp )
1132          DEALLOCATE ( rrtm_reice )
1133          DEALLOCATE ( rrtm_reliq )
1134          DEALLOCATE ( rrtm_lw_taucld )
1135          DEALLOCATE ( rrtm_lw_tauaer )
[1691]1136
[1585]1137          DEALLOCATE ( rrtm_lwdflx  )
[1691]1138          DEALLOCATE ( rrtm_lwdflxc )
[1585]1139          DEALLOCATE ( rrtm_lwuflx  )
[1691]1140          DEALLOCATE ( rrtm_lwuflxc )
1141          DEALLOCATE ( rrtm_lwuflx_dt )
1142          DEALLOCATE ( rrtm_lwuflxc_dt )
[1585]1143          DEALLOCATE ( rrtm_lwhr  )
1144          DEALLOCATE ( rrtm_lwhrc )
[1691]1145
[1585]1146          DEALLOCATE ( rrtm_sw_taucld )
1147          DEALLOCATE ( rrtm_sw_ssacld )
1148          DEALLOCATE ( rrtm_sw_asmcld )
1149          DEALLOCATE ( rrtm_sw_fsfcld )
1150          DEALLOCATE ( rrtm_sw_tauaer )
1151          DEALLOCATE ( rrtm_sw_ssaaer )
1152          DEALLOCATE ( rrtm_sw_asmaer ) 
[1691]1153          DEALLOCATE ( rrtm_sw_ecaer )   
1154 
[1585]1155          DEALLOCATE ( rrtm_swdflx  )
[1691]1156          DEALLOCATE ( rrtm_swdflxc )
[1585]1157          DEALLOCATE ( rrtm_swuflx  )
[1691]1158          DEALLOCATE ( rrtm_swuflxc )
[1585]1159          DEALLOCATE ( rrtm_swhr  )
1160          DEALLOCATE ( rrtm_swhrc )
[1691]1161
[1585]1162       ENDIF
1163
1164!
1165!--    Open file for reading
1166       nc_stat = NF90_OPEN( rrtm_input_file, NF90_NOWRITE, id )
1167       CALL handle_netcdf_error( 'netcdf', 549 )
1168
1169!
1170!--    Inquire dimension of z axis and save in nz_snd
1171       nc_stat = NF90_INQ_DIMID( id, "Pressure", id_dim_zrad )
1172       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim_zrad, len = nz_snd )
1173       CALL handle_netcdf_error( 'netcdf', 551 )
1174
1175!
1176! !--    Allocate temporary array for storing pressure data
[1701]1177       ALLOCATE( hyp_snd_tmp(1:nz_snd) )
[1585]1178       hyp_snd_tmp = 0.0_wp
1179
1180
1181!--    Read pressure from file
1182       nc_stat = NF90_INQ_VARID( id, "Pressure", id_var )
[1691]1183       nc_stat = NF90_GET_VAR( id, id_var, hyp_snd_tmp(:), start = (/1/),      &
[1585]1184                               count = (/nz_snd/) )
1185       CALL handle_netcdf_error( 'netcdf', 552 )
1186
1187!
1188!--    Allocate temporary array for storing temperature data
[1701]1189       ALLOCATE( t_snd_tmp(1:nz_snd) )
[1585]1190       t_snd_tmp = 0.0_wp
1191
1192!
1193!--    Read temperature from file
1194       nc_stat = NF90_INQ_VARID( id, "ReferenceTemperature", id_var )
[1691]1195       nc_stat = NF90_GET_VAR( id, id_var, t_snd_tmp(:), start = (/1/),        &
[1585]1196                               count = (/nz_snd/) )
1197       CALL handle_netcdf_error( 'netcdf', 553 )
1198
1199!
1200!--    Calculate start of sounding data
1201       nz_snd_start = nz_snd + 1
[1701]1202       nz_snd_end   = nz_snd + 1
[1585]1203
1204!
1205!--    Start filling vertical dimension at 10hPa above the model domain (hyp is
1206!--    in Pa, hyp_snd in hPa).
1207       DO  k = 1, nz_snd
[1691]1208          IF ( hyp_snd_tmp(k) < ( hyp(nzt+1) - 1000.0_wp) * 0.01_wp )  THEN
[1585]1209             nz_snd_start = k
1210             EXIT
1211          END IF
1212       END DO
1213
[1691]1214       IF ( nz_snd_start <= nz_snd )  THEN
[1701]1215          nz_snd_end = nz_snd
[1585]1216       END IF
1217
1218
1219!
1220!--    Calculate of total grid points for RRTMG calculations
[1701]1221       nzt_rad = nzt + nz_snd_end - nz_snd_start + 1
[1585]1222
1223!
1224!--    Save data above LES domain in hyp_snd, t_snd and q_snd
1225!--    Note: q_snd_tmp is not calculated at the moment (dry residual atmosphere)
1226       ALLOCATE( hyp_snd(nzb+1:nzt_rad) )
1227       ALLOCATE( t_snd(nzb+1:nzt_rad)   )
1228       ALLOCATE( q_snd(nzb+1:nzt_rad)   )
1229       hyp_snd = 0.0_wp
1230       t_snd = 0.0_wp
1231       q_snd = 0.0_wp
1232
[1757]1233       hyp_snd(nzt+2:nzt_rad) = hyp_snd_tmp(nz_snd_start+1:nz_snd_end)
1234       t_snd(nzt+2:nzt_rad)   = t_snd_tmp(nz_snd_start+1:nz_snd_end)
[1585]1235
1236       nc_stat = NF90_CLOSE( id )
1237
1238!
1239!--    Calculate pressure levels on zu and zw grid. Sounding data is added at
1240!--    top of the LES domain. This routine does not consider horizontal or
1241!--    vertical variability of pressure and temperature
1242       ALLOCATE ( rrtm_play(0:0,nzb+1:nzt_rad+1)   )
1243       ALLOCATE ( rrtm_plev(0:0,nzb+1:nzt_rad+2)   )
1244
[1691]1245       t_surface = pt_surface * ( surface_pressure / 1000.0_wp )**0.286_wp
[1585]1246       DO k = nzb+1, nzt+1
1247          rrtm_play(0,k) = hyp(k) * 0.01_wp
1248          rrtm_plev(0,k) = surface_pressure * ( (t_surface - g/cp * zw(k-1)) / &
1249                         t_surface )**(1.0_wp/0.286_wp)
1250       ENDDO
1251
1252       DO k = nzt+2, nzt_rad
1253          rrtm_play(0,k) = hyp_snd(k)
1254          rrtm_plev(0,k) = 0.5_wp * ( rrtm_play(0,k) + rrtm_play(0,k-1) )
1255       ENDDO
1256       rrtm_plev(0,nzt_rad+1) = MAX( 0.5 * hyp_snd(nzt_rad),                   &
1257                                   1.5 * hyp_snd(nzt_rad)                      &
1258                                 - 0.5 * hyp_snd(nzt_rad-1) )
1259       rrtm_plev(0,nzt_rad+2)  = MIN( 1.0E-4_wp,                               &
1260                                      0.25_wp * rrtm_plev(0,nzt_rad+1) )
1261
1262       rrtm_play(0,nzt_rad+1) = 0.5 * rrtm_plev(0,nzt_rad+1)
1263
1264!
1265!--    Calculate temperature/humidity levels at top of the LES domain.
1266!--    Currently, the temperature is taken from sounding data (might lead to a
1267!--    temperature jump at interface. To do: Humidity is currently not
1268!--    calculated above the LES domain.
1269       ALLOCATE ( rrtm_tlay(0:0,nzb+1:nzt_rad+1)   )
1270       ALLOCATE ( rrtm_tlev(0:0,nzb+1:nzt_rad+2)   )
1271       ALLOCATE ( rrtm_h2ovmr(0:0,nzb+1:nzt_rad+1) )
1272
1273       DO k = nzt+8, nzt_rad
1274          rrtm_tlay(0,k)   = t_snd(k)
1275          rrtm_h2ovmr(0,k) = q_snd(k)
1276       ENDDO
[1691]1277       rrtm_tlay(0,nzt_rad+1) = 2.0_wp * rrtm_tlay(0,nzt_rad)                 &
1278                                - rrtm_tlay(0,nzt_rad-1)
[1585]1279       DO k = nzt+9, nzt_rad+1
1280          rrtm_tlev(0,k)   = rrtm_tlay(0,k-1) + (rrtm_tlay(0,k)                &
1281                             - rrtm_tlay(0,k-1))                               &
1282                             / ( rrtm_play(0,k) - rrtm_play(0,k-1) )           &
1283                             * ( rrtm_plev(0,k) - rrtm_play(0,k-1) )
1284       ENDDO
1285       rrtm_h2ovmr(0,nzt_rad+1) = rrtm_h2ovmr(0,nzt_rad)
1286
1287       rrtm_tlev(0,nzt_rad+2)   = 2.0_wp * rrtm_tlay(0,nzt_rad+1)              &
1288                                  - rrtm_tlev(0,nzt_rad)
1289!
1290!--    Allocate remaining RRTMG arrays
1291       ALLOCATE ( rrtm_cicewp(0:0,nzb+1:nzt_rad+1) )
1292       ALLOCATE ( rrtm_cldfr(0:0,nzb+1:nzt_rad+1) )
1293       ALLOCATE ( rrtm_cliqwp(0:0,nzb+1:nzt_rad+1) )
1294       ALLOCATE ( rrtm_reice(0:0,nzb+1:nzt_rad+1) )
1295       ALLOCATE ( rrtm_reliq(0:0,nzb+1:nzt_rad+1) )
1296       ALLOCATE ( rrtm_lw_taucld(1:nbndlw+1,0:0,nzb+1:nzt_rad+1) )
1297       ALLOCATE ( rrtm_lw_tauaer(0:0,nzb+1:nzt_rad+1,1:nbndlw+1) )
1298       ALLOCATE ( rrtm_sw_taucld(1:nbndsw+1,0:0,nzb+1:nzt_rad+1) )
1299       ALLOCATE ( rrtm_sw_ssacld(1:nbndsw+1,0:0,nzb+1:nzt_rad+1) )
1300       ALLOCATE ( rrtm_sw_asmcld(1:nbndsw+1,0:0,nzb+1:nzt_rad+1) )
1301       ALLOCATE ( rrtm_sw_fsfcld(1:nbndsw+1,0:0,nzb+1:nzt_rad+1) )
1302       ALLOCATE ( rrtm_sw_tauaer(0:0,nzb+1:nzt_rad+1,1:nbndsw+1) )
1303       ALLOCATE ( rrtm_sw_ssaaer(0:0,nzb+1:nzt_rad+1,1:nbndsw+1) )
1304       ALLOCATE ( rrtm_sw_asmaer(0:0,nzb+1:nzt_rad+1,1:nbndsw+1) ) 
1305       ALLOCATE ( rrtm_sw_ecaer(0:0,nzb+1:nzt_rad+1,1:naerec+1) )   
1306
1307!
1308!--    The ice phase is currently not considered in PALM
1309       rrtm_cicewp = 0.0_wp
1310       rrtm_reice  = 0.0_wp
1311
1312!
1313!--    Set other parameters (move to NAMELIST parameters in the future)
1314       rrtm_lw_tauaer = 0.0_wp
1315       rrtm_lw_taucld = 0.0_wp
1316       rrtm_sw_taucld = 0.0_wp
1317       rrtm_sw_ssacld = 0.0_wp
1318       rrtm_sw_asmcld = 0.0_wp
1319       rrtm_sw_fsfcld = 0.0_wp
1320       rrtm_sw_tauaer = 0.0_wp
1321       rrtm_sw_ssaaer = 0.0_wp
1322       rrtm_sw_asmaer = 0.0_wp
1323       rrtm_sw_ecaer  = 0.0_wp
1324
1325
1326       ALLOCATE ( rrtm_swdflx(0:0,nzb:nzt_rad+1)  )
1327       ALLOCATE ( rrtm_swuflx(0:0,nzb:nzt_rad+1)  )
1328       ALLOCATE ( rrtm_swhr(0:0,nzb+1:nzt_rad+1)  )
1329       ALLOCATE ( rrtm_swuflxc(0:0,nzb:nzt_rad+1) )
1330       ALLOCATE ( rrtm_swdflxc(0:0,nzb:nzt_rad+1) )
1331       ALLOCATE ( rrtm_swhrc(0:0,nzb+1:nzt_rad+1) )
1332
1333       rrtm_swdflx  = 0.0_wp
1334       rrtm_swuflx  = 0.0_wp
1335       rrtm_swhr    = 0.0_wp 
1336       rrtm_swuflxc = 0.0_wp
1337       rrtm_swdflxc = 0.0_wp
1338       rrtm_swhrc   = 0.0_wp
1339
1340       ALLOCATE ( rrtm_lwdflx(0:0,nzb:nzt_rad+1)  )
1341       ALLOCATE ( rrtm_lwuflx(0:0,nzb:nzt_rad+1)  )
1342       ALLOCATE ( rrtm_lwhr(0:0,nzb+1:nzt_rad+1)  )
1343       ALLOCATE ( rrtm_lwuflxc(0:0,nzb:nzt_rad+1) )
1344       ALLOCATE ( rrtm_lwdflxc(0:0,nzb:nzt_rad+1) )
1345       ALLOCATE ( rrtm_lwhrc(0:0,nzb+1:nzt_rad+1) )
1346
1347       rrtm_lwdflx  = 0.0_wp
1348       rrtm_lwuflx  = 0.0_wp
1349       rrtm_lwhr    = 0.0_wp 
1350       rrtm_lwuflxc = 0.0_wp
1351       rrtm_lwdflxc = 0.0_wp
1352       rrtm_lwhrc   = 0.0_wp
1353
[1691]1354       ALLOCATE ( rrtm_lwuflx_dt(0:0,nzb:nzt_rad+1) )
1355       ALLOCATE ( rrtm_lwuflxc_dt(0:0,nzb:nzt_rad+1) )
[1585]1356
[1709]1357       rrtm_lwuflx_dt = 0.0_wp
[1691]1358       rrtm_lwuflxc_dt = 0.0_wp
1359
[1585]1360    END SUBROUTINE read_sounding_data
1361
1362
1363!------------------------------------------------------------------------------!
1364! Description:
1365! ------------
[1682]1366!> Read trace gas data from file
[1585]1367!------------------------------------------------------------------------------!
1368    SUBROUTINE read_trace_gas_data
1369
1370       USE netcdf_control
1371       USE rrsw_ncpar
1372
1373       IMPLICIT NONE
1374
[1691]1375       INTEGER(iwp), PARAMETER :: num_trace_gases = 9 !< number of trace gases (absorbers)
[1585]1376
[1691]1377       CHARACTER(LEN=5), DIMENSION(num_trace_gases), PARAMETER ::              & !< trace gas names
[1585]1378           trace_names = (/'O3   ', 'CO2  ', 'CH4  ', 'N2O  ', 'O2   ',        &
1379                           'CFC11', 'CFC12', 'CFC22', 'CCL4 '/)
1380
[1691]1381       INTEGER(iwp) :: id,     & !< NetCDF id
1382                       k,      & !< loop index
1383                       m,      & !< loop index
1384                       n,      & !< loop index
1385                       nabs,   & !< number of absorbers
1386                       np,     & !< number of pressure levels
1387                       id_abs, & !< NetCDF id of the respective absorber
1388                       id_dim, & !< NetCDF id of asborber's dimension
1389                       id_var    !< NetCDf id ot the absorber
[1585]1390
1391       REAL(wp) :: p_mls_l, p_mls_u, p_wgt_l, p_wgt_u, p_mls_m
1392
1393
[1682]1394       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  p_mls,         & !< pressure levels for the absorbers
1395                                                 rrtm_play_tmp, & !< temporary array for pressure zu-levels
1396                                                 rrtm_plev_tmp, & !< temporary array for pressure zw-levels
1397                                                 trace_path_tmp   !< temporary array for storing trace gas path data
[1585]1398
[1682]1399       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  trace_mls,      & !< array for storing the absorber amounts
1400                                                 trace_mls_path, & !< array for storing trace gas path data
1401                                                 trace_mls_tmp     !< temporary array for storing trace gas data
[1585]1402
1403
1404!
1405!--    In case of updates, deallocate arrays first (sufficient to check one
1406!--    array as the others are automatically allocated)
1407       IF ( ALLOCATED ( rrtm_o3vmr ) )  THEN
1408          DEALLOCATE ( rrtm_o3vmr  )
1409          DEALLOCATE ( rrtm_co2vmr )
1410          DEALLOCATE ( rrtm_ch4vmr )
1411          DEALLOCATE ( rrtm_n2ovmr )
1412          DEALLOCATE ( rrtm_o2vmr  )
1413          DEALLOCATE ( rrtm_cfc11vmr )
1414          DEALLOCATE ( rrtm_cfc12vmr )
1415          DEALLOCATE ( rrtm_cfc22vmr )
1416          DEALLOCATE ( rrtm_ccl4vmr  )
1417       ENDIF
1418
1419!
1420!--    Allocate trace gas profiles
1421       ALLOCATE ( rrtm_o3vmr(0:0,1:nzt_rad+1)  )
1422       ALLOCATE ( rrtm_co2vmr(0:0,1:nzt_rad+1) )
1423       ALLOCATE ( rrtm_ch4vmr(0:0,1:nzt_rad+1) )
1424       ALLOCATE ( rrtm_n2ovmr(0:0,1:nzt_rad+1) )
1425       ALLOCATE ( rrtm_o2vmr(0:0,1:nzt_rad+1)  )
1426       ALLOCATE ( rrtm_cfc11vmr(0:0,1:nzt_rad+1) )
1427       ALLOCATE ( rrtm_cfc12vmr(0:0,1:nzt_rad+1) )
1428       ALLOCATE ( rrtm_cfc22vmr(0:0,1:nzt_rad+1) )
1429       ALLOCATE ( rrtm_ccl4vmr(0:0,1:nzt_rad+1)  )
1430
1431!
1432!--    Open file for reading
1433       nc_stat = NF90_OPEN( rrtm_input_file, NF90_NOWRITE, id )
1434       CALL handle_netcdf_error( 'netcdf', 549 )
1435!
1436!--    Inquire dimension ids and dimensions
1437       nc_stat = NF90_INQ_DIMID( id, "Pressure", id_dim )
1438       CALL handle_netcdf_error( 'netcdf', 550 )
1439       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, len = np) 
1440       CALL handle_netcdf_error( 'netcdf', 550 )
1441
1442       nc_stat = NF90_INQ_DIMID( id, "Absorber", id_dim )
1443       CALL handle_netcdf_error( 'netcdf', 550 )
1444       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, len = nabs ) 
1445       CALL handle_netcdf_error( 'netcdf', 550 )
1446   
1447
1448!
1449!--    Allocate pressure, and trace gas arrays     
1450       ALLOCATE( p_mls(1:np) )
1451       ALLOCATE( trace_mls(1:num_trace_gases,1:np) ) 
1452       ALLOCATE( trace_mls_tmp(1:nabs,1:np) ) 
1453
1454
1455       nc_stat = NF90_INQ_VARID( id, "Pressure", id_var )
1456       CALL handle_netcdf_error( 'netcdf', 550 )
1457       nc_stat = NF90_GET_VAR( id, id_var, p_mls )
1458       CALL handle_netcdf_error( 'netcdf', 550 )
1459
1460       nc_stat = NF90_INQ_VARID( id, "AbsorberAmountMLS", id_var )
1461       CALL handle_netcdf_error( 'netcdf', 550 )
1462       nc_stat = NF90_GET_VAR( id, id_var, trace_mls_tmp )
1463       CALL handle_netcdf_error( 'netcdf', 550 )
1464
1465
1466!
1467!--    Write absorber amounts (mls) to trace_mls
1468       DO n = 1, num_trace_gases
1469          CALL getAbsorberIndex( TRIM( trace_names(n) ), id_abs )
1470
1471          trace_mls(n,1:np) = trace_mls_tmp(id_abs,1:np)
1472
1473!
1474!--       Replace missing values by zero
1475          WHERE ( trace_mls(n,:) > 2.0_wp ) 
1476             trace_mls(n,:) = 0.0_wp
1477          END WHERE
1478       END DO
1479
1480       DEALLOCATE ( trace_mls_tmp )
1481
1482       nc_stat = NF90_CLOSE( id )
1483       CALL handle_netcdf_error( 'netcdf', 551 )
1484
1485!
1486!--    Add extra pressure level for calculations of the trace gas paths
1487       ALLOCATE ( rrtm_play_tmp(1:nzt_rad+1) )
1488       ALLOCATE ( rrtm_plev_tmp(1:nzt_rad+2) )
1489
1490       rrtm_play_tmp(1:nzt_rad)   = rrtm_play(0,1:nzt_rad) 
1491       rrtm_plev_tmp(1:nzt_rad+1) = rrtm_plev(0,1:nzt_rad+1)
1492       rrtm_play_tmp(nzt_rad+1)   = rrtm_plev(0,nzt_rad+1) * 0.5_wp
1493       rrtm_plev_tmp(nzt_rad+2)   = MIN( 1.0E-4_wp, 0.25_wp                    &
1494                                         * rrtm_plev(0,nzt_rad+1) )
1495 
1496!
1497!--    Calculate trace gas path (zero at surface) with interpolation to the
1498!--    sounding levels
1499       ALLOCATE ( trace_mls_path(1:nzt_rad+2,1:num_trace_gases) )
1500
1501       trace_mls_path(nzb+1,:) = 0.0_wp
1502       
1503       DO k = nzb+2, nzt_rad+2
1504          DO m = 1, num_trace_gases
1505             trace_mls_path(k,m) = trace_mls_path(k-1,m)
1506
1507!
1508!--          When the pressure level is higher than the trace gas pressure
1509!--          level, assume that
[1691]1510             IF ( rrtm_plev_tmp(k-1) > p_mls(1) )  THEN             
[1585]1511               
1512                trace_mls_path(k,m) = trace_mls_path(k,m) + trace_mls(m,1)     &
1513                                      * ( rrtm_plev_tmp(k-1)                   &
1514                                          - MAX( p_mls(1), rrtm_plev_tmp(k) )  &
1515                                        ) / g
1516             ENDIF
1517
1518!
1519!--          Integrate for each sounding level from the contributing p_mls
1520!--          levels
1521             DO n = 2, np
1522!
1523!--             Limit p_mls so that it is within the model level
1524                p_mls_u = MIN( rrtm_plev_tmp(k-1),                             &
1525                          MAX( rrtm_plev_tmp(k), p_mls(n) ) )
1526                p_mls_l = MIN( rrtm_plev_tmp(k-1),                             &
1527                          MAX( rrtm_plev_tmp(k), p_mls(n-1) ) )
1528
[1691]1529                IF ( p_mls_l > p_mls_u )  THEN
[1585]1530
1531!
1532!--                Calculate weights for interpolation
1533                   p_mls_m = 0.5_wp * (p_mls_l + p_mls_u)
1534                   p_wgt_u = (p_mls(n-1) - p_mls_m) / (p_mls(n-1) - p_mls(n))
1535                   p_wgt_l = (p_mls_m - p_mls(n))   / (p_mls(n-1) - p_mls(n))
1536
1537!
1538!--                Add level to trace gas path
1539                   trace_mls_path(k,m) = trace_mls_path(k,m)                   &
1540                                         +  ( p_wgt_u * trace_mls(m,n)         &
1541                                            + p_wgt_l * trace_mls(m,n-1) )     &
[1691]1542                                         * (p_mls_l - p_mls_u) / g
[1585]1543                ENDIF
1544             ENDDO
1545
[1691]1546             IF ( rrtm_plev_tmp(k) < p_mls(np) )  THEN
[1585]1547                trace_mls_path(k,m) = trace_mls_path(k,m) + trace_mls(m,np)    &
1548                                      * ( MIN( rrtm_plev_tmp(k-1), p_mls(np) ) &
1549                                          - rrtm_plev_tmp(k)                   &
1550                                        ) / g 
1551             ENDIF 
[1496]1552          ENDDO
1553       ENDDO
1554
1555
[1585]1556!
1557!--    Prepare trace gas path profiles
1558       ALLOCATE ( trace_path_tmp(1:nzt_rad+1) )
[1496]1559
[1585]1560       DO m = 1, num_trace_gases
1561
1562          trace_path_tmp(1:nzt_rad+1) = ( trace_mls_path(2:nzt_rad+2,m)        &
1563                                       - trace_mls_path(1:nzt_rad+1,m) ) * g   &
1564                                       / ( rrtm_plev_tmp(1:nzt_rad+1)          &
1565                                       - rrtm_plev_tmp(2:nzt_rad+2) )
1566
1567!
1568!--       Save trace gas paths to the respective arrays
1569          SELECT CASE ( TRIM( trace_names(m) ) )
1570
1571             CASE ( 'O3' )
1572
1573                rrtm_o3vmr(0,:) = trace_path_tmp(:)
1574
1575             CASE ( 'CO2' )
1576
1577                rrtm_co2vmr(0,:) = trace_path_tmp(:)
1578
1579             CASE ( 'CH4' )
1580
1581                rrtm_ch4vmr(0,:) = trace_path_tmp(:)
1582
1583             CASE ( 'N2O' )
1584
1585                rrtm_n2ovmr(0,:) = trace_path_tmp(:)
1586
1587             CASE ( 'O2' )
1588
1589                rrtm_o2vmr(0,:) = trace_path_tmp(:)
1590
1591             CASE ( 'CFC11' )
1592
1593                rrtm_cfc11vmr(0,:) = trace_path_tmp(:)
1594
1595             CASE ( 'CFC12' )
1596
1597                rrtm_cfc12vmr(0,:) = trace_path_tmp(:)
1598
1599             CASE ( 'CFC22' )
1600
1601                rrtm_cfc22vmr(0,:) = trace_path_tmp(:)
1602
1603             CASE ( 'CCL4' )
1604
1605                rrtm_ccl4vmr(0,:) = trace_path_tmp(:)
1606
1607             CASE DEFAULT
1608
1609          END SELECT
1610
1611       ENDDO
1612
1613       DEALLOCATE ( trace_path_tmp )
1614       DEALLOCATE ( trace_mls_path )
1615       DEALLOCATE ( rrtm_play_tmp )
1616       DEALLOCATE ( rrtm_plev_tmp )
1617       DEALLOCATE ( trace_mls )
1618       DEALLOCATE ( p_mls )
1619
1620    END SUBROUTINE read_trace_gas_data
1621
1622#endif
1623
1624
[1551]1625!------------------------------------------------------------------------------!
1626! Description:
1627! ------------
[1682]1628!> Calculate temperature tendency due to radiative cooling/heating.
1629!> Cache-optimized version.
[1551]1630!------------------------------------------------------------------------------!
[1585]1631    SUBROUTINE radiation_tendency_ij ( i, j, tend )
[1496]1632
[1585]1633       USE cloud_parameters,                                                   &
[1691]1634           ONLY:  pt_d_t
[1551]1635
[1585]1636       IMPLICIT NONE
1637
[1691]1638       INTEGER(iwp) :: i, j, k !< loop indices
[1585]1639
[1691]1640       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: tend !< pt tendency term
[1585]1641
1642#if defined ( __rrtmg )
1643!
[1691]1644!--    Calculate tendency based on heating rate
[1585]1645       DO k = nzb+1, nzt+1
[1691]1646          tend(k,j,i) = tend(k,j,i) + (rad_lw_hr(k,j,i) + rad_sw_hr(k,j,i))    &
1647                                      * pt_d_t(k) * d_seconds_hour
[1585]1648       ENDDO
1649
1650#endif
1651
1652    END SUBROUTINE radiation_tendency_ij
1653
1654
[1551]1655!------------------------------------------------------------------------------!
1656! Description:
1657! ------------
[1682]1658!> Calculate temperature tendency due to radiative cooling/heating.
1659!> Vector-optimized version
[1551]1660!------------------------------------------------------------------------------!
[1585]1661    SUBROUTINE radiation_tendency ( tend )
[1551]1662
[1585]1663       USE cloud_parameters,                                                   &
[1691]1664           ONLY:  pt_d_t
[1551]1665
[1585]1666       USE indices,                                                            &
1667           ONLY:  nxl, nxr, nyn, nys
1668
1669       IMPLICIT NONE
1670
[1691]1671       INTEGER(iwp) :: i, j, k !< loop indices
[1585]1672
[1691]1673       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: tend !< pt tendency term
[1585]1674
1675#if defined ( __rrtmg )
[1691]1676!
1677!--    Calculate tendency based on heating rate
[1585]1678       DO  i = nxl, nxr
1679          DO  j = nys, nyn
1680             DO k = nzb+1, nzt+1
[1691]1681                tend(k,j,i) = tend(k,j,i) + ( rad_lw_hr(k,j,i)                 &
1682                                            +  rad_sw_hr(k,j,i) ) * pt_d_t(k)  &
1683                                            * d_seconds_hour
[1585]1684             ENDDO
1685         ENDDO
1686       ENDDO
1687#endif
1688
1689    END SUBROUTINE radiation_tendency
1690
[1496]1691 END MODULE radiation_model_mod
Note: See TracBrowser for help on using the repository browser.