source: palm/trunk/SOURCE/disturb_heatflux.f90 @ 1323

Last change on this file since 1323 was 1323, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.4 KB
Line 
1 SUBROUTINE disturb_heatflux
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: disturb_heatflux.f90 1323 2014-03-20 17:09:54Z raasch $
27!
28! 1322 2014-03-20 16:38:49Z raasch
29! REAL constants defined as wp-kind
30!
31! 1320 2014-03-20 08:40:49Z raasch
32! ONLY-attribute added to USE-statements,
33! kind-parameters added to all INTEGER and REAL declaration statements,
34! kinds are defined in new module kinds,
35! revision history before 2012 removed,
36! comment fields (!:) to be used for variable explanations added to
37! all variable declaration statements
38!
39! 1036 2012-10-22 13:43:42Z raasch
40! code put under GPL (PALM 3.9)
41!
42! Revision 1.1  1998/03/25 20:03:47  raasch
43! Initial revision
44!
45!
46! Description:
47! ------------
48! Generate random, normally distributed heatflux values and store them as the
49! near-surface heatflux.
50! On parallel computers, too, this random generator is called at all grid points
51! of the total array in order to guarantee the same random distribution of the
52! total array regardless of the number of processors used during the model run.
53!------------------------------------------------------------------------------!
54
55    USE arrays_3d,                                                             &
56        ONLY:  shf
57       
58    USE control_parameters,                                                    &
59        ONLY:  iran, surface_heatflux, wall_heatflux
60       
61    USE cpulog,                                                                &
62        ONLY:  cpu_log, log_point
63       
64    USE kinds
65   
66    USE indices,                                                               &
67        ONLY:  nx, nxl, nxr, ny, nyn, nys, nzb_s_inner
68
69    IMPLICIT NONE
70
71    INTEGER(iwp) ::  j  !:
72    INTEGER(iwp) ::  i  !:
73   
74    REAL(wp) ::  random_gauss  !:
75    REAL(wp) ::  randomnumber  !:
76
77
78    CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
79
80!
81!-- Generate random disturbances and store them
82    DO  i = 0, nx
83       DO  j = 0, ny
84          randomnumber = random_gauss( iran, 5.0_wp )
85          IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  nyn >= j )   &
86          THEN
87             IF ( nzb_s_inner(j,i) == 0 )  THEN
88                shf(j,i) = randomnumber * surface_heatflux
89             ELSE
90!
91!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
92                shf(j,i) = randomnumber * wall_heatflux(0)
93             ENDIF
94          ENDIF
95       ENDDO
96    ENDDO
97
98!
99!-- Exchange lateral boundary conditions for the heatflux array
100    CALL exchange_horiz_2d( shf )
101
102    CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
103
104
105 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.