source: palm/trunk/SOURCE/disturb_field.f90 @ 420

Last change on this file since 420 was 420, checked in by franke, 14 years ago

collision of cloud droplets has changed in advec_particles
bugfixes in advec_particles and collision_efficiency
change in disturb_field to make runs reproducible on HLRN

  • Property svn:keywords set to Id
File size: 5.7 KB
Line 
1 SUBROUTINE disturb_field( nzb_uv_inner, dist1, field )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! A loop has been splitted to make runs reproducible on HLRN systems
7!
8! Former revisions:
9! -----------------
10! $Id: disturb_field.f90 420 2010-01-13 15:10:53Z franke $
11!
12! 75 2007-03-22 09:54:05Z raasch
13! xrp, ynp eliminated, 2nd+3rd argument removed from exchange horiz
14!
15! RCS Log replace by Id keyword, revision history cleaned up
16!
17! Revision 1.11  2006/08/04 14:31:59  raasch
18! izuf renamed iran
19!
20! Revision 1.1  1998/02/04 15:40:45  raasch
21! Initial revision
22!
23!
24! Description:
25! ------------
26! Imposing a random perturbation on a 3D-array.
27! On parallel computers, the random number generator is as well called for all
28! gridpoints of the total domain to ensure, regardless of the number of PEs
29! used, that the elements of the array have the same values in the same
30! order in every case. The perturbation range is steered by dist_range.
31!------------------------------------------------------------------------------!
32
33    USE control_parameters
34    USE cpulog
35    USE grid_variables
36    USE indices
37    USE interfaces
38    USE random_function_mod
39
40    IMPLICIT NONE
41
42    INTEGER ::  i, j, k
43    INTEGER ::  nzb_uv_inner(nys-1:nyn+1,nxl-1:nxr+1)
44
45    REAL    ::  randomnumber,                             &
46                dist1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
47                field(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
48    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  dist2
49
50
51    CALL cpu_log( log_point(20), 'disturb_field', 'start' )
52
53!
54!-- Create an additional temporary array and initialize the arrays needed
55!-- to store the disturbance
56    ALLOCATE( dist2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
57    dist1 = 0.0
58    dist2 = 0.0
59
60!
61!-- Create the random perturbation and store it on temporary array
62    IF ( random_generator == 'numerical-recipes' )  THEN
63       DO  i = dist_nxl(dist_range), dist_nxr(dist_range)
64          DO  j = dist_nys(dist_range), dist_nyn(dist_range)
65             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
66                randomnumber = 3.0 * disturbance_amplitude * &
67                               ( random_function( iran ) - 0.5 )
68                IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  &
69                     nyn >= j ) &
70                THEN
71                   dist1(k,j,i) = randomnumber
72                ENDIF
73             ENDDO
74          ENDDO
75       ENDDO
76    ELSEIF ( random_generator == 'system-specific' )  THEN
77       DO  i = dist_nxl(dist_range), dist_nxr(dist_range)
78          DO  j = dist_nys(dist_range), dist_nyn(dist_range)
79             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
80#if defined( __nec )
81                randomnumber = 3.0 * disturbance_amplitude * &
82                               ( RANDOM( 0 ) - 0.5 )
83#else
84                CALL RANDOM_NUMBER( randomnumber )
85                randomnumber = 3.0 * disturbance_amplitude * &
86                                ( randomnumber - 0.5 )
87#endif
88                IF ( nxl <= i .AND. nxr >= i .AND. nys <= j .AND. nyn >= j ) &
89                THEN
90                   dist1(k,j,i) = randomnumber
91                ENDIF
92             ENDDO
93          ENDDO
94       ENDDO
95
96    ENDIF
97
98!
99!-- Exchange of ghost points for the random perturbation
100
101    CALL exchange_horiz( dist1 )
102
103!
104!-- Applying the Shuman filter in order to smooth the perturbations.
105!-- Neighboured grid points in all three directions are used for the
106!-- filter operation.
107!-- Loop has been splitted to make runs reproducible on HLRN systems using
108!-- compiler option -O3
109     DO  i = nxl, nxr
110        DO  j = nys, nyn
111          DO  k = disturbance_level_ind_b-1, disturbance_level_ind_t+1
112             dist2(k,j,i) = ( dist1(k,j,i-1) + dist1(k,j,i+1) &
113                            + dist1(k,j+1,i) + dist1(k+1,j,i) &
114                            ) / 12.0
115          ENDDO
116          DO  k = disturbance_level_ind_b-1, disturbance_level_ind_t+1
117              dist2(k,j,i) = dist2(k,j,i) + ( dist1(k,j-1,i) + dist1(k-1,j,i)  &
118                            + 6.0 * dist1(k,j,i)                               &
119                            ) / 12.0
120          ENDDO
121        ENDDO
122     ENDDO
123
124!
125!-- Exchange of ghost points for the filtered perturbation.
126!-- Afterwards, filter operation and exchange of ghost points are repeated.
127    CALL exchange_horiz( dist2 )
128
129    DO  i = nxl, nxr
130       DO  j = nys, nyn
131          DO  k = disturbance_level_ind_b-2, disturbance_level_ind_t+2
132             dist1(k,j,i) = ( dist2(k,j,i-1) + dist2(k,j,i+1) + dist2(k,j-1,i) &
133                            + dist2(k,j+1,i) + dist2(k+1,j,i) + dist2(k-1,j,i) &
134                            + 6.0 * dist2(k,j,i)                               &
135                            ) / 12.0
136          ENDDO
137       ENDDO
138    ENDDO
139
140    CALL exchange_horiz( dist1 )
141
142!
143!-- Remove perturbations below topography (including one gridpoint above it
144!-- in order to allow for larger timesteps at the beginning of the simulation
145!-- (diffusion criterion))
146    IF ( TRIM( topography ) /= 'flat' )  THEN
147       DO  i = nxl-1, nxr+1
148          DO  j = nys-1, nyn+1
149             dist1(nzb:nzb_uv_inner(j,i)+1,j,i) = 0.0
150          ENDDO
151       ENDDO
152    ENDIF
153
154!
155!-- Random perturbation is added to the array to be disturbed.
156    DO  i = nxl-1, nxr+1
157       DO  j = nys-1, nyn+1
158          DO  k = disturbance_level_ind_b-2, disturbance_level_ind_t+2
159             field(k,j,i) = field(k,j,i) + dist1(k,j,i)
160          ENDDO
161       ENDDO
162    ENDDO
163
164!
165!-- Deallocate the temporary array
166    DEALLOCATE( dist2 )
167
168!
169!-- Set a flag, which indicates that a random perturbation is imposed
170    disturbance_created = .TRUE.
171
172
173    CALL cpu_log( log_point(20), 'disturb_field', 'stop' )
174
175
176 END SUBROUTINE disturb_field
Note: See TracBrowser for help on using the repository browser.