source: palm/trunk/SOURCE/disturb_field.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: 6.2 KB
Line 
1 SUBROUTINE disturb_field( nzb_uv_inner, dist1, field, xrp, ynp )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: disturb_field.f90,v $
11! Revision 1.11  2006/08/04 14:31:59  raasch
12! izuf renamed iran
13!
14! Revision 1.10  2006/02/23 12:14:06  raasch
15! Additional argument nzb_uv_inner (no perturbations below the topography)
16!
17! Revision 1.9  2005/03/26 20:18:30  raasch
18! Arguments for non-cyclic boundary conditions added to argument list and to
19! argument list of routine exchange_horiz.
20! Perturbations can be imposed for different ranges (steered by dist_range).
21!
22! Revision 1.8  2003/10/29 08:48:51  raasch
23! Module random_function_mod is used
24!
25! Revision 1.7  2003/03/14 13:41:48  raasch
26! Different random number generators available
27!
28! Revision 1.6  2001/03/30 07:22:26  raasch
29! Translation of remaining German identifiers (variables, subroutines, etc.)
30!
31! Revision 1.5  2001/01/25 06:59:38  raasch
32! Module interfaces added (missing this interface caused errors on machines
33! other than Cray)
34!
35! Revision 1.4  2001/01/22 06:32:49  raasch
36! Module test_variables removed
37!
38! Revision 1.3  2000/07/03 12:59:03  raasch
39! All comments translated into English
40!
41! Revision 1.2  1998/07/06 12:13:01  raasch
42! + USE test_variables
43!
44! Revision 1.1  1998/02/04 15:40:45  raasch
45! Initial revision
46!
47!
48! Description:
49! ------------
50! Imposing a random perturbation on a 3D-array.
51! On parallel computers, the random number generator is as well called for all
52! gridpoints of the total domain to ensure, regardless of the number of PEs
53! used, that the elements of the array have the same values in the same
54! order in every case. The perturbation range is steered by dist_range.
55!------------------------------------------------------------------------------!
56
57    USE control_parameters
58    USE cpulog
59    USE grid_variables
60    USE indices
61    USE interfaces
62    USE random_function_mod
63
64    IMPLICIT NONE
65
66    INTEGER ::  i, j, k, xrp, ynp
67    INTEGER ::  nzb_uv_inner(nys-1:nyn+1,nxl-1:nxr+1)
68
69    REAL    ::  randomnumber,                             &
70                dist1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
71                field(nzb:nzt+1,nys-1:nyn+ynp+1,nxl-1:nxr+xrp+1)
72    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  dist2
73
74
75    CALL cpu_log( log_point(20), 'disturb_field', 'start' )
76
77!
78!-- Create an additional temporary array and initialize the arrays needed
79!-- to store the disturbance
80    ALLOCATE( dist2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
81    dist1 = 0.0
82    dist2 = 0.0
83
84!
85!-- Create the random perturbation and store it on temporary array
86    IF ( random_generator == 'numerical-recipes' )  THEN
87       DO  i = dist_nxl(dist_range), dist_nxr(dist_range)
88          DO  j = dist_nys(dist_range), dist_nyn(dist_range)
89             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
90                randomnumber = 3.0 * disturbance_amplitude * &
91                               ( random_function( iran ) - 0.5 )
92                IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  &
93                     nyn >= j ) &
94                THEN
95                   dist1(k,j,i) = randomnumber
96                ENDIF
97             ENDDO
98          ENDDO
99       ENDDO
100    ELSEIF ( random_generator == 'system-specific' )  THEN
101       DO  i = dist_nxl(dist_range), dist_nxr(dist_range)
102          DO  j = dist_nys(dist_range), dist_nyn(dist_range)
103             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
104#if defined( __nec )
105                randomnumber = 3.0 * disturbance_amplitude * &
106                               ( RANDOM( 0 ) - 0.5 )
107#else
108                CALL RANDOM_NUMBER( randomnumber )
109                randomnumber = 3.0 * disturbance_amplitude * &
110                                ( randomnumber - 0.5 )
111#endif
112                IF ( nxl <= i .AND. nxr >= i .AND. nys <= j .AND. nyn >= j ) &
113                THEN
114                   dist1(k,j,i) = randomnumber
115                ENDIF
116             ENDDO
117          ENDDO
118       ENDDO
119
120    ENDIF
121
122!
123!-- Exchange of ghost points for the random perturbation
124    CALL exchange_horiz( dist1, 0, 0 )
125
126!
127!-- Applying the Shuman filter in order to smooth the perturbations.
128!-- Neighboured grid points in all three directions are used for the
129!-- filter operation.
130    DO  i = nxl, nxr
131       DO  j = nys, nyn
132          DO  k = disturbance_level_ind_b-1, disturbance_level_ind_t+1
133             dist2(k,j,i) = ( dist1(k,j,i-1) + dist1(k,j,i+1) + dist1(k,j-1,i) &
134                            + dist1(k,j+1,i) + dist1(k+1,j,i) + dist1(k-1,j,i) &
135                            + 6.0 * dist1(k,j,i)                               &
136                            ) / 12.0
137          ENDDO
138       ENDDO
139    ENDDO
140
141!
142!-- Exchange of ghost points for the filtered perturbation.
143!-- Afterwards, filter operation and exchange of ghost points are repeated.
144    CALL exchange_horiz( dist2, 0, 0 )
145    DO  i = nxl, nxr
146       DO  j = nys, nyn
147          DO  k = disturbance_level_ind_b-2, disturbance_level_ind_t+2
148             dist1(k,j,i) = ( dist2(k,j,i-1) + dist2(k,j,i+1) + dist2(k,j-1,i) &
149                            + dist2(k,j+1,i) + dist2(k+1,j,i) + dist2(k-1,j,i) &
150                            + 6.0 * dist2(k,j,i)                               &
151                            ) / 12.0
152          ENDDO
153       ENDDO
154    ENDDO
155    CALL exchange_horiz( dist1, 0, 0 )
156
157!
158!-- Remove perturbations below topography (including one gridpoint above it
159!-- in order to allow for larger timesteps at the beginning of the simulation
160!-- (diffusion criterion))
161    IF ( TRIM( topography ) /= 'flat' )  THEN
162       DO  i = nxl-1, nxr+1
163          DO  j = nys-1, nyn+1
164             dist1(nzb:nzb_uv_inner(j,i)+1,j,i) = 0.0
165          ENDDO
166       ENDDO
167    ENDIF
168
169!
170!-- Random perturbation is added to the array to be disturbed.
171    DO  i = nxl-1, nxr+1
172       DO  j = nys-1, nyn+1
173          DO  k = disturbance_level_ind_b-2, disturbance_level_ind_t+2
174             field(k,j,i) = field(k,j,i) + dist1(k,j,i)
175          ENDDO
176       ENDDO
177    ENDDO
178
179!
180!-- Deallocate the temporary array
181    DEALLOCATE( dist2 )
182
183!
184!-- Set a flag, which indicates that a random perturbation is imposed
185    disturbance_created = .TRUE.
186
187
188    CALL cpu_log( log_point(20), 'disturb_field', 'stop' )
189
190
191 END SUBROUTINE disturb_field
Note: See TracBrowser for help on using the repository browser.