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

Last change on this file since 4313 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 4.4 KB
RevLine 
[1682]1!> @file disturb_heatflux.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[2000]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.
[1036]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!
[3655]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[1320]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1322]21! ------------------
[1354]22!
[2233]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: disturb_heatflux.f90 4182 2019-08-22 15:20:23Z suehring $
[4182]27! Corrected "Former revisions" section
28!
29! 3761 2019-02-25 15:31:42Z raasch
[3761]30! unsed variables removed
31!
32! 3719 2019-02-06 13:10:18Z kanani
[3719]33! Moved log_points out of subroutine into time_integration for better overview.
34!
35! 3655 2019-01-07 16:51:22Z knoop
[3241]36! unused variable removed
[1321]37!
[4182]38! Revision 1.1  1998/03/25 20:03:47  raasch
39! Initial revision
40!
41!
[1]42! Description:
43! ------------
[1682]44!> Generate random, normally distributed heatflux values and store them as the
45!> near-surface heatflux.
[1]46!------------------------------------------------------------------------------!
[2232]47 SUBROUTINE disturb_heatflux( surf )
[1682]48 
[1]49
[1320]50    USE arrays_3d,                                                             &
[2232]51        ONLY:  heatflux_input_conversion
[1320]52       
53    USE control_parameters,                                                    &
[2232]54        ONLY:  iran, surface_heatflux, random_generator, wall_heatflux
[1320]55       
56    USE kinds
57   
58    USE indices,                                                               &
[2232]59        ONLY:  nzb
[1]60
[2232]61    USE random_generator_parallel,                                             &
62        ONLY:  random_number_parallel, random_seed_parallel, random_dummy,     &
[3241]63               seq_random_array
[2232]64
65    USE surface_mod,                                                           &
66        ONLY:  surf_type
67
[1]68    IMPLICIT NONE
69
[2232]70    INTEGER(iwp) ::  i  !< grid index, x direction
71    INTEGER(iwp) ::  j  !< grid index, y direction
72    INTEGER(iwp) ::  k  !< grid index, z direction
73    INTEGER(iwp) ::  m  !< loop variables over surface elements
[1320]74   
[1682]75    REAL(wp) ::  random_gauss  !<
76    REAL(wp) ::  randomnumber  !<
[1]77
[2232]78    TYPE(surf_type) ::  surf   !< surface-type variable
[1]79
[2232]80
[1]81!
[2232]82!-- Generate random disturbances and store them. Note, if
83!-- random_generator /= 'random-parallel' it is not guaranteed to obtain 
84!-- the same random distribution if the number of processors is changed.
85    IF ( random_generator /= 'random-parallel' )  THEN
86
87       DO  m = 1, surf%ns
88
89          k = surf%k(m)
90
91          randomnumber = random_gauss( iran, 5.0_wp )     
[1]92!
[2232]93!--       k-1 is topography top index. If this is 0, set surface heatflux. Over
94!--       topography surface_heatflux is replaced by wall_heatflux(0).
95          IF ( k-1 == 0 )  THEN
96             surf%shf(m) = randomnumber * surface_heatflux                     &
97                              * heatflux_input_conversion(nzb)
98          ELSE
99             surf%shf(m) = randomnumber * wall_heatflux(0)                     &
100                              * heatflux_input_conversion(k-1)
[1]101          ENDIF
102       ENDDO
[2232]103    ELSE
[1]104
[2232]105       DO  m = 1, surf%ns
106
107          i = surf%i(m)
108          j = surf%j(m)
109          k = surf%k(m)
110
111          CALL random_seed_parallel( put=seq_random_array(:, j, i) )
112          CALL random_number_parallel( random_dummy )   
[1]113!
[2232]114!--       k-1 is topography top index. If this is 0, set surface heatflux. Over
115!--       topography surface_heatflux is replaced by wall_heatflux(0).
116          IF ( k-1 == 0 )  THEN
117             surf%shf(m) = ( random_dummy - 0.5_wp ) * surface_heatflux        &
118                              * heatflux_input_conversion(nzb)
119          ELSE
120             surf%shf(m) = ( random_dummy - 0.5_wp ) * wall_heatflux(0)        &
121                              * heatflux_input_conversion(k-1)
122          ENDIF
[1]123
[2232]124          CALL random_seed_parallel( get=seq_random_array(:, j, i) )
125
126       ENDDO
127
128    ENDIF
129
[1]130
131 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.