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

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

REAL functions and a lot of REAL constants provided with KIND-attribute,
some small bugfixes

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