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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 3.3 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:
[1]21! -----------------
[1320]22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! old module precision_kind is removed,
26! revision history before 2012 removed,
27! comment fields (!:) to be used for variable explanations added to
28! all variable declaration statements
[1]29!
30! Former revisions:
31! -----------------
[3]32! $Id: disturb_heatflux.f90 1320 2014-03-20 08:40:49Z raasch $
[556]33!
[1037]34! 1036 2012-10-22 13:43:42Z raasch
35! code put under GPL (PALM 3.9)
36!
[1]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
[1320]50    USE arrays_3d,                                                             &
51        ONLY:  shf
52       
53    USE control_parameters,                                                    &
54        ONLY:  iran, surface_heatflux, wall_heatflux
55       
56    USE cpulog,                                                                &
57        ONLY:  cpu_log, log_point
58       
59    USE kinds
60   
61    USE indices,                                                               &
62        ONLY:  nx, nxl, nxr, ny, nyn, nys, nzb_s_inner
[1]63
64    IMPLICIT NONE
65
[1320]66    INTEGER(iwp) ::  j  !:
67    INTEGER(iwp) ::  i  !:
68   
69    REAL(wp) ::  random_gauss  !:
70    REAL(wp) ::  randomnumber  !:
[1]71
72
73    CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
74
75!
76!-- Generate random disturbances and store them
77    DO  i = 0, nx
78       DO  j = 0, ny
79          randomnumber = random_gauss( iran, 5.0 )
[1320]80          IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  nyn >= j )   &
[1]81          THEN
82             IF ( nzb_s_inner(j,i) == 0 )  THEN
83                shf(j,i) = randomnumber * surface_heatflux
[555]84             ELSE
[1]85!
86!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
87                shf(j,i) = randomnumber * wall_heatflux(0)
88             ENDIF
89          ENDIF
90       ENDDO
91    ENDDO
92
93!
94!-- Exchange lateral boundary conditions for the heatflux array
95    CALL exchange_horiz_2d( shf )
96
97    CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
98
99
100 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.