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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1!> @file disturb_heatflux.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: disturb_heatflux.f90 4180 2019-08-21 14:37:54Z scharf $
27! unsed variables removed
28!
29! 3719 2019-02-06 13:10:18Z kanani
30! Moved log_points out of subroutine into time_integration for better overview.
31!
32! 3655 2019-01-07 16:51:22Z knoop
33! unused variable removed
34!
35!
36! Description:
37! ------------
38!> Generate random, normally distributed heatflux values and store them as the
39!> near-surface heatflux.
40!------------------------------------------------------------------------------!
41 SUBROUTINE disturb_heatflux( surf )
42 
43
44    USE arrays_3d,                                                             &
45        ONLY:  heatflux_input_conversion
46       
47    USE control_parameters,                                                    &
48        ONLY:  iran, surface_heatflux, random_generator, wall_heatflux
49       
50    USE kinds
51   
52    USE indices,                                                               &
53        ONLY:  nzb
54
55    USE random_generator_parallel,                                             &
56        ONLY:  random_number_parallel, random_seed_parallel, random_dummy,     &
57               seq_random_array
58
59    USE surface_mod,                                                           &
60        ONLY:  surf_type
61
62    IMPLICIT NONE
63
64    INTEGER(iwp) ::  i  !< grid index, x direction
65    INTEGER(iwp) ::  j  !< grid index, y direction
66    INTEGER(iwp) ::  k  !< grid index, z direction
67    INTEGER(iwp) ::  m  !< loop variables over surface elements
68   
69    REAL(wp) ::  random_gauss  !<
70    REAL(wp) ::  randomnumber  !<
71
72    TYPE(surf_type) ::  surf   !< surface-type variable
73
74
75!
76!-- Generate random disturbances and store them. Note, if
77!-- random_generator /= 'random-parallel' it is not guaranteed to obtain 
78!-- the same random distribution if the number of processors is changed.
79    IF ( random_generator /= 'random-parallel' )  THEN
80
81       DO  m = 1, surf%ns
82
83          k = surf%k(m)
84
85          randomnumber = random_gauss( iran, 5.0_wp )     
86!
87!--       k-1 is topography top index. If this is 0, set surface heatflux. Over
88!--       topography surface_heatflux is replaced by wall_heatflux(0).
89          IF ( k-1 == 0 )  THEN
90             surf%shf(m) = randomnumber * surface_heatflux                     &
91                              * heatflux_input_conversion(nzb)
92          ELSE
93             surf%shf(m) = randomnumber * wall_heatflux(0)                     &
94                              * heatflux_input_conversion(k-1)
95          ENDIF
96       ENDDO
97    ELSE
98
99       DO  m = 1, surf%ns
100
101          i = surf%i(m)
102          j = surf%j(m)
103          k = surf%k(m)
104
105          CALL random_seed_parallel( put=seq_random_array(:, j, i) )
106          CALL random_number_parallel( random_dummy )   
107!
108!--       k-1 is topography top index. If this is 0, set surface heatflux. Over
109!--       topography surface_heatflux is replaced by wall_heatflux(0).
110          IF ( k-1 == 0 )  THEN
111             surf%shf(m) = ( random_dummy - 0.5_wp ) * surface_heatflux        &
112                              * heatflux_input_conversion(nzb)
113          ELSE
114             surf%shf(m) = ( random_dummy - 0.5_wp ) * wall_heatflux(0)        &
115                              * heatflux_input_conversion(k-1)
116          ENDIF
117
118          CALL random_seed_parallel( get=seq_random_array(:, j, i) )
119
120       ENDDO
121
122    ENDIF
123
124
125 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.