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

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

added beta version of a land surface model and a simple radiation model for clear sky conditions

  • Property svn:keywords set to Id
File size: 6.7 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! Initial revision
23!
24! Former revisions:
25! -----------------
26! $Id: radiation_model.f90 1496 2014-12-02 17:25:50Z maronga $
27!
28!
29! Description:
30! ------------
31! Radiation model(s), to be used e.g. with the land surface scheme
32!------------------------------------------------------------------------------!
33
34    USE arrays_3d,                                                             &
35        ONLY: pt
36
37    USE control_parameters,                                                    &
38        ONLY: phi, surface_pressure, time_since_reference_point
39
40    USE indices,                                                               &
41        ONLY:  nxlg, nxrg, nyng, nysg, nzb_s_inner
42
43    USE kinds
44
45
46    IMPLICIT NONE
47
48    INTEGER(iwp) :: i, j, k
49
50
51    INTEGER(iwp) :: day_init = 1 !: day of the year at model start
52
53    LOGICAL :: radiation = .FALSE.  !: flag parameter indicating wheather the radiation model is used
54
55    REAL(wp), PARAMETER :: SW_0 = 1368.0, &       !: solar constant 
56                           pi = 3.14159265358979323_wp, &
57                           sigma_SB  = 5.67E-8_wp !: Stefan-Boltzmann constant
58 
59    REAL(wp) :: albedo = 0.2_wp,             & !: NAMELIST alpha
60                dt_radiation = 9999999.9_wp, &
61                exn,                         & !: Exner function
62                lon = 0.0_wp,                & !: longitude in radians
63                lat = 0.0_wp,                & !: latitude in radians
64                decl_1,                      & !: declination coef. 1
65                decl_2,                      & !: declination coef. 2
66                decl_3,                      & !: declination coef. 3
67                time_utc,                    & !: current time in UTC
68                time_utc_init = 0.0_wp,      & !: UTC time at model start
69                day,                         & !: current day of the year
70                lambda = 0.0_wp,             & !: longitude in degrees
71                declination,                 & !: solar declination angle
72                hour_angle,                  & !: solar hour angle
73                time_radiation = 0.0_wp,     &
74                zenith,                      & !: solar zenith angle
75                sky_trans                      !: sky transmissivity
76
77    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: &
78                alpha,                       & !: surface albedo
79                Rn,                          & !: net radiation at the surface
80                LW_in,                       & !: incoming longwave radiation
81                LW_out,                      & !: outgoing longwave radiation
82                SW_in,                       & !: incoming shortwave radiation
83                SW_out                         !: outgoing shortwave radiation
84
85
86    INTERFACE init_radiation
87       MODULE PROCEDURE init_radiation
88    END INTERFACE init_radiation
89
90    INTERFACE lsm_radiation
91       MODULE PROCEDURE lsm_radiation
92    END INTERFACE lsm_radiation
93
94    SAVE
95
96    PRIVATE
97
98    PUBLIC albedo, day_init, dt_radiation, init_radiation, lambda,             &
99           lsm_radiation, Rn, radiation, SW_in, sigma_SB, time_radiation,      &
100           time_utc_init 
101
102
103
104 CONTAINS
105
106!------------------------------------------------------------------------------!
107! Description:
108! ------------
109!-- Initialization of the radiation model
110!------------------------------------------------------------------------------!
111    SUBROUTINE init_radiation
112   
113
114       IMPLICIT NONE
115
116       ALLOCATE ( alpha(nysg:nyng,nxlg:nxrg) )
117       ALLOCATE ( Rn(nysg:nyng,nxlg:nxrg) )
118       ALLOCATE ( LW_in(nysg:nyng,nxlg:nxrg) )
119       ALLOCATE ( LW_out(nysg:nyng,nxlg:nxrg) )
120       ALLOCATE ( SW_in(nysg:nyng,nxlg:nxrg) )
121       ALLOCATE ( SW_out(nysg:nyng,nxlg:nxrg) )
122
123       alpha = albedo
124
125!
126!--    Calculate radiation scheme constants
127       decl_1 = SIN(23.45_wp * pi / 180.0_wp)
128       decl_2 = 2.0 * pi / 365.0_wp
129       decl_3 = decl_2 * 81.0_wp
130
131!
132!--    Calculate latitude and longitude angles (lat and lon, respectively)
133       lat = phi * pi / 180.0_wp
134       lon = lambda * pi / 180.0_wp
135
136       RETURN
137
138    END SUBROUTINE init_radiation
139
140
141!------------------------------------------------------------------------------!
142! Description:
143! ------------
144!-- A simple clear sky radiation model
145!------------------------------------------------------------------------------!
146    SUBROUTINE lsm_radiation
147   
148
149       IMPLICIT NONE
150
151!
152!--    Calculate current day and time based on the initial values and simulation
153!--    time
154       day = day_init + FLOOR( (time_utc_init + time_since_reference_point)    &
155                               / 86400.0_wp )
156       time_utc = MOD((time_utc_init + time_since_reference_point), 86400.0_wp)
157
158
159!
160!--    Calculate solar declination and hour angle   
161       declination = ASIN( decl_1 * SIN(decl_2 * day - decl_3) )
162       hour_angle  = 2.0_wp * pi * (time_utc / 86400.0_wp) + lon - pi
163
164!
165!--    Calculate zenith angle
166       zenith = SIN(lat)*SIN(declination) + COS(lat) * COS(declination)        &
167                                            * COS(hour_angle)
168       zenith = MAX(0.0_wp,zenith)
169
170!
171!--    Calculate sky transmissivity
172       sky_trans = 0.6_wp + 0.2_wp * zenith
173
174!
175!--    Calculate value of the Exner function
176       exn = (surface_pressure / 1000.0_wp )**0.286_wp
177
178!
179!--    Calculate radiation fluxes and net radiation (Rn) for each grid point
180       DO i = nxlg, nxrg
181          DO j = nysg, nyng
182
183             k = nzb_s_inner(j,i)
184             SW_in(j,i)  = SW_0 * sky_trans * zenith
185             SW_out(j,i) = - alpha(j,i) * SW_in(j,i)
186             LW_out(j,i) = - sigma_SB * (pt(k,j,i) * exn)**4
187             LW_in(j,i)  = 0.8 * sigma_SB * (pt(k+1,j,i) * exn)**4
188             Rn(j,i)     = SW_in(j,i) + SW_out(j,i) + LW_in(j,i) + LW_out(j,i)
189
190          ENDDO
191       ENDDO
192
193       RETURN
194
195    END SUBROUTINE lsm_radiation
196
197
198
199 END MODULE radiation_model_mod
Note: See TracBrowser for help on using the repository browser.