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

Last change on this file since 1572 was 1572, checked in by maronga, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 9.4 KB
Line 
1 MODULE radiation_model_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: radiation_model.f90 1572 2015-03-12 16:14:19Z maronga $
27!
28! 1571 2015-03-12 16:12:49Z maronga
29! Added missing KIND attribute. Removed upper-case variable names
30!
31! 1551 2015-03-03 14:18:16Z maronga
32! Added support for data output. Various variables have been renamed. Added
33! interface for different radiation schemes (currently: clear-sky, constant, and
34! RRTM (not yet implemented).
35!
36! 1496 2014-12-02 17:25:50Z maronga
37! Initial revision
38!
39!
40! Description:
41! ------------
42! Radiation model(s), to be used e.g. with the land surface scheme
43!------------------------------------------------------------------------------!
44
45    USE arrays_3d,                                                             &
46        ONLY: pt
47
48    USE control_parameters,                                                    &
49        ONLY: phi, surface_pressure, time_since_reference_point
50
51    USE indices,                                                               &
52        ONLY:  nxlg, nxrg, nyng, nysg, nzb_s_inner
53
54    USE kinds
55
56    USE netcdf_control,                                                        &
57        ONLY:  dots_label, dots_num, dots_unit
58
59
60    IMPLICIT NONE
61
62    CHARACTER(10) :: radiation_scheme = 'clear-sky' ! 'constant', 'clear-sky', or 'rrtm'
63
64    INTEGER(iwp) :: i, j, k
65
66
67    INTEGER(iwp) :: day_init     = 172,  & !: day of the year at model start (21/06)
68                    dots_rad     = 0,    & !: starting index for timeseries output
69                    irad_scheme  = 0
70
71    LOGICAL :: radiation = .FALSE.  !: flag parameter indicating wheather the radiation model is used
72
73    REAL(wp), PARAMETER :: sw_0 = 1368.0_wp, &    !: solar constant 
74                           pi = 3.14159265358979323_wp, &
75                           sigma_sb  = 5.67E-8_wp !: Stefan-Boltzmann constant
76 
77    REAL(wp) :: albedo = 0.2_wp,             & !: NAMELIST alpha
78                dt_radiation = 0.0_wp,       & !: radiation model timestep
79                exn,                         & !: Exner function
80                lon = 0.0_wp,                & !: longitude in radians
81                lat = 0.0_wp,                & !: latitude in radians
82                decl_1,                      & !: declination coef. 1
83                decl_2,                      & !: declination coef. 2
84                decl_3,                      & !: declination coef. 3
85                time_utc,                    & !: current time in UTC
86                time_utc_init = 43200.0_wp,  & !: UTC time at model start (noon)
87                day,                         & !: current day of the year
88                lambda = 0.0_wp,             & !: longitude in degrees
89                declination,                 & !: solar declination angle
90                net_radiation = 0.0_wp,      & !: net radiation at surface
91                hour_angle,                  & !: solar hour angle
92                time_radiation = 0.0_wp,     &
93                zenith,                      & !: solar zenith angle
94                sky_trans                      !: sky transmissivity
95
96    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: &
97                alpha,                       & !: surface albedo
98                rad_net,                     & !: net radiation at the surface
99                rad_net_av,                  & !: average of rad_net
100                rad_lw_in,                   & !: incoming longwave radiation
101                rad_lw_out,                  & !: outgoing longwave radiation
102                rad_sw_in,                   & !: incoming shortwave radiation
103                rad_sw_in_av,                & !: average of rad_sw_in
104                rad_sw_out                     !: outgoing shortwave radiation
105
106
107    INTERFACE init_radiation
108       MODULE PROCEDURE init_radiation
109    END INTERFACE init_radiation
110
111    INTERFACE radiation_clearsky
112       MODULE PROCEDURE radiation_clearsky
113    END INTERFACE radiation_clearsky
114
115    INTERFACE radiation_constant
116       MODULE PROCEDURE radiation_constant
117    END INTERFACE radiation_constant
118
119    INTERFACE radiation_rrtm
120       MODULE PROCEDURE radiation_rrtm
121    END INTERFACE radiation_rrtm
122
123
124    SAVE
125
126    PRIVATE
127
128    PUBLIC albedo, day_init, dots_rad, dt_radiation, init_radiation,           &
129           irad_scheme, lambda, net_radiation, rad_net, rad_net_av, radiation, &
130           radiation_clearsky, radiation_constant, radiation_rrtm,             &
131           radiation_scheme, rad_sw_in, rad_sw_in_av, sigma_sb,                &
132           time_radiation, time_utc_init 
133
134
135
136 CONTAINS
137
138!------------------------------------------------------------------------------!
139! Description:
140! ------------
141!-- Initialization of the radiation model
142!------------------------------------------------------------------------------!
143    SUBROUTINE init_radiation
144   
145
146       IMPLICIT NONE
147
148       ALLOCATE ( alpha(nysg:nyng,nxlg:nxrg) )
149       ALLOCATE ( rad_net(nysg:nyng,nxlg:nxrg) )
150       ALLOCATE ( rad_lw_in(nysg:nyng,nxlg:nxrg) )
151       ALLOCATE ( rad_lw_out(nysg:nyng,nxlg:nxrg) )
152       ALLOCATE ( rad_sw_in(nysg:nyng,nxlg:nxrg) )
153       ALLOCATE ( rad_sw_out(nysg:nyng,nxlg:nxrg) )
154
155       rad_sw_in  = 0.0_wp
156       rad_sw_out = 0.0_wp
157       rad_lw_in  = 0.0_wp
158       rad_lw_out = 0.0_wp
159       rad_net    = 0.0_wp
160
161       alpha = albedo
162
163!
164!--    Fix net radiation in case of radiation_scheme = 'constant'
165       IF ( irad_scheme == 0 )  THEN
166          rad_net = net_radiation
167!
168!--    Calculate radiation scheme constants
169       ELSEIF ( irad_scheme == 1 .OR. irad_scheme == 2 )  THEN
170          decl_1 = SIN(23.45_wp * pi / 180.0_wp)
171          decl_2 = 2.0_wp * pi / 365.0_wp
172          decl_3 = decl_2 * 81.0_wp
173!
174!--       Calculate latitude and longitude angles (lat and lon, respectively)
175          lat = phi * pi / 180.0_wp
176          lon = lambda * pi / 180.0_wp
177       ENDIF
178!
179!--    Add timeseries for radiation model
180       dots_label(dots_num+1) = "rad_net"
181       dots_label(dots_num+2) = "rad_sw_in"
182       dots_unit(dots_num+1:dots_num+2) = "W/m2"
183
184       dots_rad  = dots_num + 1
185       dots_num  = dots_num + 2
186
187       RETURN
188
189    END SUBROUTINE init_radiation
190
191
192!------------------------------------------------------------------------------!
193! Description:
194! ------------
195!-- A simple clear sky radiation model
196!------------------------------------------------------------------------------!
197    SUBROUTINE radiation_clearsky
198   
199
200       IMPLICIT NONE
201
202!
203!--    Calculate current day and time based on the initial values and simulation
204!--    time
205       day = day_init + FLOOR( (time_utc_init + time_since_reference_point)    &
206                               / 86400.0_wp )
207       time_utc = MOD((time_utc_init + time_since_reference_point), 86400.0_wp)
208
209
210!
211!--    Calculate solar declination and hour angle   
212       declination = ASIN( decl_1 * SIN(decl_2 * day - decl_3) )
213       hour_angle  = 2.0_wp * pi * (time_utc / 86400.0_wp) + lon - pi
214
215!
216!--    Calculate zenith angle
217       zenith = SIN(lat) * SIN(declination) + COS(lat) * COS(declination)       &
218                                            * COS(hour_angle)
219       zenith = MAX(0.0_wp,zenith)
220
221!
222!--    Calculate sky transmissivity
223       sky_trans = 0.6_wp + 0.2_wp * zenith
224
225!
226!--    Calculate value of the Exner function
227       exn = (surface_pressure / 1000.0_wp )**0.286_wp
228
229!
230!--    Calculate radiation fluxes and net radiation (rad_net) for each grid
231!--    point
232       DO i = nxlg, nxrg
233          DO j = nysg, nyng
234
235             k = nzb_s_inner(j,i)
236             rad_sw_in(j,i)  = sw_0 * sky_trans * zenith
237             rad_sw_out(j,i) = - alpha(j,i) * rad_sw_in(j,i)
238             rad_lw_out(j,i) = - sigma_sb * (pt(k,j,i) * exn)**4
239             rad_lw_in(j,i)  = 0.8_wp * sigma_sb * (pt(k+1,j,i) * exn)**4
240             rad_net(j,i)    = rad_sw_in(j,i) + rad_sw_out(j,i)                &
241                                + rad_lw_in(j,i) + rad_lw_out(j,i)
242
243          ENDDO
244       ENDDO
245
246       RETURN
247
248    END SUBROUTINE radiation_clearsky
249
250!------------------------------------------------------------------------------!
251! Description:
252! ------------
253!-- Prescribed net radiation
254!------------------------------------------------------------------------------!
255    SUBROUTINE radiation_constant
256
257       rad_net = net_radiation
258
259    END SUBROUTINE radiation_constant
260
261!------------------------------------------------------------------------------!
262! Description:
263! ------------
264!-- Implementation of the RRTM radiation_scheme
265!------------------------------------------------------------------------------!
266    SUBROUTINE radiation_rrtm
267
268
269    END SUBROUTINE radiation_rrtm
270
271 END MODULE radiation_model_mod
Note: See TracBrowser for help on using the repository browser.