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

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

last commit documented

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