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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 2.4 KB
Line 
1 SUBROUTINE disturb_heatflux
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: disturb_heatflux.f90,v $
11! Revision 1.7  2006/08/04 14:35:07  raasch
12! Additional parameter in function random_gauss which limits the range of the
13! created random numbers, izuf renamed iran
14!
15! Revision 1.6  2006/02/23 12:14:38  raasch
16! Over topography surface_heatflux is replaced by wall_heatflux(0)
17!
18! Revision 1.5  2001/03/30 07:22:44  raasch
19! Translation of remaining German identifiers (variables, subroutines, etc.)
20!
21! Revision 1.4  2001/01/22 06:34:34  raasch
22! Module test_variables removed
23!
24! Revision 1.3  2000/12/20 11:57:38  letzel
25! All comments translated into English.
26!
27! Revision 1.2  1998/07/06 12:13:19  raasch
28! + USE test_variables
29!
30! Revision 1.1  1998/03/25 20:03:47  raasch
31! Initial revision
32!
33!
34! Description:
35! ------------
36! Generate random, normally distributed heatflux values and store them as the
37! near-surface heatflux.
38! On parallel computers, too, this random generator is called at all grid points
39! of the total array in order to guarantee the same random distribution of the
40! total array regardless of the number of processors used during the model run.
41!------------------------------------------------------------------------------!
42
43    USE arrays_3d
44    USE control_parameters
45    USE cpulog
46    USE grid_variables
47    USE indices
48    USE interfaces
49
50    IMPLICIT NONE
51
52    INTEGER ::  i, j
53    REAL    ::  random_gauss, randomnumber
54
55
56    CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
57
58!
59!-- Generate random disturbances and store them
60    DO  i = 0, nx
61       DO  j = 0, ny
62          randomnumber = random_gauss( iran, 5.0 )
63          IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  nyn >= j ) &
64          THEN
65             IF ( nzb_s_inner(j,i) == 0 )  THEN
66                shf(j,i) = randomnumber * surface_heatflux
67!
68!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
69                shf(j,i) = randomnumber * wall_heatflux(0)
70             ELSE
71             ENDIF
72          ENDIF
73       ENDDO
74    ENDDO
75
76!
77!-- Exchange lateral boundary conditions for the heatflux array
78    CALL exchange_horiz_2d( shf )
79
80    CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
81
82
83 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.