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

Last change on this file since 1036 was 1036, checked in by raasch, 11 years ago

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 2.8 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: disturb_heatflux.f90 1036 2012-10-22 13:43:42Z raasch $
27!
28! 555 2010-09-07 07:32:53Z raasch
29! Bugfix in if statement
30!
31! RCS Log replace by Id keyword, revision history cleaned up
32!
33! Revision 1.7  2006/08/04 14:35:07  raasch
34! Additional parameter in function random_gauss which limits the range of the
35! created random numbers, izuf renamed iran
36!
37! Revision 1.1  1998/03/25 20:03:47  raasch
38! Initial revision
39!
40!
41! Description:
42! ------------
43! Generate random, normally distributed heatflux values and store them as the
44! near-surface heatflux.
45! On parallel computers, too, this random generator is called at all grid points
46! of the total array in order to guarantee the same random distribution of the
47! total array regardless of the number of processors used during the model run.
48!------------------------------------------------------------------------------!
49
50    USE arrays_3d
51    USE control_parameters
52    USE cpulog
53    USE grid_variables
54    USE indices
55    USE interfaces
56
57    IMPLICIT NONE
58
59    INTEGER ::  i, j
60    REAL    ::  random_gauss, randomnumber
61
62
63    CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
64
65!
66!-- Generate random disturbances and store them
67    DO  i = 0, nx
68       DO  j = 0, ny
69          randomnumber = random_gauss( iran, 5.0 )
70          IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  nyn >= j ) &
71          THEN
72             IF ( nzb_s_inner(j,i) == 0 )  THEN
73                shf(j,i) = randomnumber * surface_heatflux
74             ELSE
75!
76!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
77                shf(j,i) = randomnumber * wall_heatflux(0)
78             ENDIF
79          ENDIF
80       ENDDO
81    ENDDO
82
83!
84!-- Exchange lateral boundary conditions for the heatflux array
85    CALL exchange_horiz_2d( shf )
86
87    CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
88
89
90 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.