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

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

land surface model released

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