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

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

last commit documented

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