source: palm/trunk/SOURCE/init_particles.f90 @ 76

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

bugs fixed for particle code and bc-scheme

  • Property svn:keywords set to Id
File size: 20.5 KB
Line 
1 SUBROUTINE init_particles
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! displacements for mpi_particle_type changed, age_m initialized,
7! particles-package is now part of the default code
8!
9! Former revisions:
10! -----------------
11! $Id: init_particles.f90 70 2007-03-18 23:46:30Z raasch $
12!
13! 16 2007-02-15 13:16:47Z raasch
14! Bugfix: MPI_REAL in MPI_ALLREDUCE replaced by MPI_INTEGER
15!
16! r4 | raasch | 2007-02-13 12:33:16 +0100 (Tue, 13 Feb 2007)
17! RCS Log replace by Id keyword, revision history cleaned up
18!
19! Revision 1.24  2007/02/11 13:00:17  raasch
20! Bugfix: allocation of tail_mask and new_tail_id in case of restart-runs
21! Bugfix: __ was missing in a cpp-directive
22!
23! Revision 1.1  1999/11/25 16:22:38  raasch
24! Initial revision
25!
26!
27! Description:
28! ------------
29! This routine initializes a set of particles and their attributes (position,
30! radius, ..). Advection of these particles is carried out by advec_particles,
31! plotting is done in data_output_dvrp.
32!------------------------------------------------------------------------------!
33
34    USE arrays_3d
35    USE control_parameters
36    USE grid_variables
37    USE indices
38    USE particle_attributes
39    USE pegrid
40    USE random_function_mod
41
42
43    IMPLICIT NONE
44
45    CHARACTER (LEN=10) ::  particle_binary_version, version_on_file
46
47    INTEGER ::  i, j, n, nn
48#if defined( __parallel )
49    INTEGER, DIMENSION(3) ::  blocklengths, displacements, types
50#endif
51    LOGICAL ::  uniform_particles_l
52    REAL    ::  factor, pos_x, pos_y, pos_z, value
53
54
55#if defined( __parallel )
56!
57!-- Define MPI derived datatype for FORTRAN datatype particle_type (see module
58!-- particle_attributes). Integer length is 4 byte, Real is 8 byte (=> total
59!-- length 100, nevertheless, 120 bytes are needed on T3E since integer seems
60!-- to be 8 bytes long there)
61    blocklengths(1)  = 19; blocklengths(2)  = 4; blocklengths(3)  =  1
62#if defined( __t3eb )
63    displacements(1) = 0; displacements(2) = 152; displacements(3) = 184
64#else
65    displacements(1) = 0; displacements(2) = 152; displacements(3) = 168
66#endif
67    types(1) = MPI_REAL
68    types(2) = MPI_INTEGER
69    types(3) = MPI_UB
70    CALL MPI_TYPE_STRUCT( 3, blocklengths, displacements, types, &
71                          mpi_particle_type, ierr )
72    CALL MPI_TYPE_COMMIT( mpi_particle_type, ierr )
73#endif
74
75!
76!-- Check the number of particle groups.
77    IF ( number_of_particle_groups > max_number_of_particle_groups )  THEN
78       PRINT*, '+++ WARNING: init_particles: ', &
79                    'max_number_of_particle_groups =', &
80               max_number_of_particle_groups
81       PRINT*, '+++          number_of_particle_groups reset to ', &
82               max_number_of_particle_groups
83       number_of_particle_groups = max_number_of_particle_groups
84    ENDIF
85
86!
87!-- Set default start positions, if necessary
88    IF ( psl(1) == 9999999.9 )  psl(1) = -0.5 * dx
89    IF ( psr(1) == 9999999.9 )  psr(1) = ( nx + 0.5 ) * dx
90    IF ( pss(1) == 9999999.9 )  pss(1) = -0.5 * dy
91    IF ( psn(1) == 9999999.9 )  psn(1) = ( ny + 0.5 ) * dy
92    IF ( psb(1) == 9999999.9 )  psb(1) = zu(nz/2)
93    IF ( pst(1) == 9999999.9 )  pst(1) = psb(1)
94
95    IF ( pdx(1) == 9999999.9  .OR.  pdx(1) == 0.0 )  pdx(1) = dx
96    IF ( pdy(1) == 9999999.9  .OR.  pdy(1) == 0.0 )  pdy(1) = dy
97    IF ( pdz(1) == 9999999.9  .OR.  pdz(1) == 0.0 )  pdz(1) = zu(2) - zu(1)
98
99    DO  j = 2, number_of_particle_groups
100       IF ( psl(j) == 9999999.9 )  psl(j) = psl(j-1)
101       IF ( psr(j) == 9999999.9 )  psr(j) = psr(j-1)
102       IF ( pss(j) == 9999999.9 )  pss(j) = pss(j-1)
103       IF ( psn(j) == 9999999.9 )  psn(j) = psn(j-1)
104       IF ( psb(j) == 9999999.9 )  psb(j) = psb(j-1)
105       IF ( pst(j) == 9999999.9 )  pst(j) = pst(j-1)
106       IF ( pdx(j) == 9999999.9  .OR.  pdx(j) == 0.0 )  pdx(j) = pdx(j-1)
107       IF ( pdy(j) == 9999999.9  .OR.  pdy(j) == 0.0 )  pdy(j) = pdy(j-1)
108       IF ( pdz(j) == 9999999.9  .OR.  pdz(j) == 0.0 )  pdz(j) = pdz(j-1)
109    ENDDO
110
111!
112!-- For the first model run of a possible job chain initialize the
113!-- particles, otherwise read the particle data from file.
114    IF ( TRIM( initializing_actions ) == 'read_restart_data'  &
115         .AND.  read_particles_from_restartfile )  THEN
116
117!
118!--    Read particle data from previous model run.
119!--    First open the input unit.
120       IF ( myid_char == '' )  THEN
121          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char, &
122                     FORM='UNFORMATTED' )
123       ELSE
124          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char, &
125                     FORM='UNFORMATTED' )
126       ENDIF
127
128!
129!--    First compare the version numbers
130       READ ( 90 )  version_on_file
131       particle_binary_version = '3.0'
132       IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
133          IF ( myid == 0 )  THEN
134             PRINT*, '+++ init_particles: version mismatch concerning data ', &
135                     'from prior run'
136             PRINT*, '        version on file    = "', TRIM( version_on_file ),&
137                     '"'
138             PRINT*, '        version in program = "', &
139                     TRIM( particle_binary_version ), '"'
140          ENDIF
141          CALL local_stop
142       ENDIF
143
144!
145!--    Read some particle parameters and the size of the particle arrays,
146!--    allocate them and read their contents.
147       READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                  &
148                    maximum_number_of_particles, maximum_number_of_tailpoints, &
149                    maximum_number_of_tails, number_of_initial_particles,      &
150                    number_of_particles, number_of_particle_groups,            &
151                    number_of_tails, particle_groups, time_prel,               &
152                    time_write_particle_data, uniform_particles
153
154       IF ( number_of_initial_particles /= 0 )  THEN
155          ALLOCATE( initial_particles(1:number_of_initial_particles) )
156          READ ( 90 )  initial_particles
157       ENDIF
158
159       ALLOCATE( prt_count(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),       &
160                 prt_start_index(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
161                 particle_mask(maximum_number_of_particles),         &
162                 particles(maximum_number_of_particles) )
163
164       READ ( 90 )  prt_count, prt_start_index
165       READ ( 90 )  particles
166
167       IF ( use_particle_tails )  THEN
168          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
169                    maximum_number_of_tails),                                 &
170                    new_tail_id(maximum_number_of_tails),                     &
171                    tail_mask(maximum_number_of_tails) )
172          READ ( 90 )  particle_tail_coordinates
173       ENDIF
174
175       CLOSE ( 90 )
176
177    ELSE
178
179!
180!--    Allocate particle arrays and set attributes of the initial set of
181!--    particles, which can be also periodically released at later times.
182!--    Also allocate array for particle tail coordinates, if needed.
183       ALLOCATE( prt_count(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),       &
184                 prt_start_index(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
185                 particle_mask(maximum_number_of_particles),         &
186                 particles(maximum_number_of_particles) )
187
188!
189!--    Initialize all particles with dummy values (otherwise errors may
190!--    occur within restart runs). The reason for this is still not clear
191!--    and may be presumably caused by errors in the respective user-interface.
192       particles = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
193                                  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
194                                  0.0, 0, 0, 0, 0 )
195       particle_groups = particle_groups_type( 0.0, 0.0, 0.0, 0.0 )
196
197!
198!--    Set the default particle size used for dvrp plots
199       IF ( dvrp_psize == 9999999.9 )  dvrp_psize = 0.2 * dx
200
201!
202!--    Set values for the density ratio and radius for all particle
203!--    groups, if necessary
204       IF ( density_ratio(1) == 9999999.9 )  density_ratio(1) = 0.0
205       IF ( radius(1)        == 9999999.9 )  radius(1) = 0.0
206       DO  i = 2, number_of_particle_groups
207          IF ( density_ratio(i) == 9999999.9 )  THEN
208             density_ratio(i) = density_ratio(i-1)
209          ENDIF
210          IF ( radius(i) == 9999999.9 )  radius(i) = radius(i-1)
211       ENDDO
212
213       DO  i = 1, number_of_particle_groups
214          IF ( density_ratio(i) /= 0.0  .AND.  radius(i) == 0 )  THEN
215             IF ( myid == 0 )  THEN
216                PRINT*, '+++ init_particles: particle group #', i, 'has a', &
217                        'density ratio /= 0 but radius = 0'
218             ENDIF
219             CALL local_stop
220          ENDIF
221          particle_groups(i)%density_ratio = density_ratio(i)
222          particle_groups(i)%radius        = radius(i)
223       ENDDO
224
225!
226!--    Calculate particle positions and store particle attributes, if
227!--    particle is situated on this PE
228       n = 0
229
230       DO  i = 1, number_of_particle_groups
231
232          pos_z = psb(i)
233
234          DO WHILE ( pos_z <= pst(i) )
235
236             pos_y = pss(i)
237
238             DO WHILE ( pos_y <= psn(i) )
239
240                IF ( pos_y >= ( nys - 0.5 ) * dy  .AND.  &
241                     pos_y <  ( nyn + 0.5 ) * dy )  THEN
242
243                   pos_x = psl(i)
244
245                   DO WHILE ( pos_x <= psr(i) )
246
247                      IF ( pos_x >= ( nxl - 0.5 ) * dx  .AND.  &
248                           pos_x <  ( nxr + 0.5 ) * dx )  THEN
249
250                         DO  j = 1, particles_per_point
251
252                            n = n + 1
253                            IF ( n > maximum_number_of_particles )  THEN
254                               PRINT*,'+++ init_particles: number of initial', &
255                                      ' particles (', n, ') exceeds'
256                               PRINT*,'    maximum_number_of_particles (',     &
257                                      maximum_number_of_particles, ') on PE ', &
258                                      myid
259#if defined( __parallel )
260                               CALL MPI_ABORT( comm2d, 9999, ierr )
261#else
262                               CALL local_stop
263#endif
264                            ENDIF
265                            particles(n)%x             = pos_x
266                            particles(n)%y             = pos_y
267                            particles(n)%z             = pos_z
268                            particles(n)%age           = 0.0
269                            particles(n)%age_m         = 0.0
270                            particles(n)%dt_sum        = 0.0
271                            particles(n)%dvrp_psize    = dvrp_psize
272                            particles(n)%e_m           = 0.0
273                            particles(n)%speed_x       = 0.0
274                            particles(n)%speed_x_sgs   = 0.0
275                            particles(n)%speed_y       = 0.0
276                            particles(n)%speed_y_sgs   = 0.0
277                            particles(n)%speed_z       = 0.0
278                            particles(n)%speed_z_sgs   = 0.0
279                            particles(n)%origin_x      = pos_x
280                            particles(n)%origin_y      = pos_y
281                            particles(n)%origin_z      = pos_z
282                            particles(n)%radius      = particle_groups(i)%radius
283                            particles(n)%weight_factor =initial_weighting_factor
284                            particles(n)%color         = 1
285                            particles(n)%group         = i
286                            particles(n)%tailpoints    = 0
287                            IF ( use_particle_tails  .AND. &
288                                 MOD( n, skip_particles_for_tail ) == 0 )  THEN
289                               number_of_tails         = number_of_tails + 1
290!
291!--                            This is a temporary provisional setting (see
292!--                            further below!)
293                               particles(n)%tail_id    = number_of_tails
294                            ELSE
295                               particles(n)%tail_id    = 0
296                            ENDIF
297
298                         ENDDO
299
300                      ENDIF
301
302                      pos_x = pos_x + pdx(i)
303
304                   ENDDO
305
306                ENDIF
307
308                pos_y = pos_y + pdy(i)
309
310             ENDDO
311
312             pos_z = pos_z + pdz(i)
313
314          ENDDO
315
316       ENDDO
317
318       number_of_initial_particles = n
319       number_of_particles         = n
320
321!
322!--    Calculate the number of particles and tails of the total domain
323#if defined( __parallel )
324       CALL MPI_ALLREDUCE( number_of_particles, total_number_of_particles, 1, &
325                           MPI_INTEGER, MPI_SUM, comm2d, ierr )
326       CALL MPI_ALLREDUCE( number_of_tails, total_number_of_tails, 1, &
327                           MPI_INTEGER, MPI_SUM, comm2d, ierr )
328#else
329       total_number_of_particles = number_of_particles
330       total_number_of_tails     = number_of_tails
331#endif
332
333!
334!--    Set a seed value for the random number generator to be exclusively
335!--    used for the particle code. The generated random numbers should be
336!--    different on the different PEs.
337       iran_part = iran_part + myid
338
339!
340!--    User modification of initial particles
341       CALL user_init_particles
342
343!
344!--    Store the initial set of particles for release at later times
345       IF ( number_of_initial_particles /= 0 )  THEN
346          ALLOCATE( initial_particles(1:number_of_initial_particles) )
347          initial_particles(1:number_of_initial_particles) = &
348                                        particles(1:number_of_initial_particles)
349       ENDIF
350
351!
352!--    Add random fluctuation to particle positions
353       IF ( random_start_position )  THEN
354
355          iran = iran + myid    ! Random positions should be different on
356                                ! different PEs
357
358          DO  n = 1, number_of_initial_particles
359             IF ( psl(particles(n)%group) /= psr(particles(n)%group) )  THEN
360                particles(n)%x = particles(n)%x + &
361                                 ( random_function( iran ) - 0.5 ) * &
362                                 pdx(particles(n)%group)
363                IF ( particles(n)%x  <=  ( nxl - 0.5 ) * dx )  THEN
364                   particles(n)%x = ( nxl - 0.4999999999 ) * dx
365                ELSEIF ( particles(n)%x  >=  ( nxr + 0.5 ) * dx )  THEN
366                   particles(n)%x = ( nxr + 0.4999999999 ) * dx
367                ENDIF
368             ENDIF
369             IF ( pss(particles(n)%group) /= psn(particles(n)%group) )  THEN
370                particles(n)%y = particles(n)%y + &
371                                 ( random_function( iran ) - 0.5 ) * &
372                                 pdy(particles(n)%group)
373                IF ( particles(n)%y  <=  ( nys - 0.5 ) * dy )  THEN
374                   particles(n)%y = ( nys - 0.4999999999 ) * dy
375                ELSEIF ( particles(n)%y  >=  ( nyn + 0.5 ) * dy )  THEN
376                   particles(n)%y = ( nyn + 0.4999999999 ) * dy
377                ENDIF
378             ENDIF
379             IF ( psb(particles(n)%group) /= pst(particles(n)%group) )  THEN
380                particles(n)%z = particles(n)%z + &
381                                 ( random_function( iran ) - 0.5 ) * &
382                                 pdz(particles(n)%group)
383             ENDIF
384          ENDDO
385       ENDIF
386
387!
388!--    Sort particles in the sequence the gridboxes are stored in the memory
389       CALL sort_particles
390
391!
392!--    Open file for statistical informations about particle conditions
393       IF ( write_particle_statistics )  THEN
394          CALL check_open( 80 )
395          WRITE ( 80, 8000 )  current_timestep_number, simulated_time, &
396                              number_of_initial_particles,             &
397                              maximum_number_of_particles
398          CALL close_file( 80 )
399       ENDIF
400
401!
402!--    Check if particles are really uniform in color and radius (dvrp_size)
403!--    (uniform_particles is preset TRUE)
404       IF ( uniform_particles )  THEN
405          IF ( number_of_initial_particles == 0 )  THEN
406             uniform_particles_l = .TRUE.
407          ELSE
408             n = number_of_initial_particles
409             IF ( MINVAL( particles(1:n)%dvrp_psize  ) ==     &
410                  MAXVAL( particles(1:n)%dvrp_psize  )  .AND. &
411                  MINVAL( particles(1:n)%color ) ==     &
412                  MAXVAL( particles(1:n)%color ) )  THEN
413                uniform_particles_l = .TRUE.
414             ELSE
415                uniform_particles_l = .FALSE.
416             ENDIF
417          ENDIF
418
419#if defined( __parallel )
420          CALL MPI_ALLREDUCE( uniform_particles_l, uniform_particles, 1, &
421                              MPI_LOGICAL, MPI_LAND, comm2d, ierr )
422#else
423          uniform_particles = uniform_particles_l
424#endif
425
426       ENDIF
427
428!
429!--    Set the beginning of the particle tails and their age
430       IF ( use_particle_tails )  THEN
431!
432!--       Choose the maximum number of tails significantly larger than the
433!--       one initially required
434          factor = 10.0
435          value  = number_of_tails
436          DO WHILE ( value / 10.0 >= 1.0 )
437             factor = factor * 10.0
438             value  = value / 10.0
439          ENDDO
440          maximum_number_of_tails = factor * INT( value )
441
442          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
443                    maximum_number_of_tails),                                 &
444                    new_tail_id(maximum_number_of_tails),                     &
445                    tail_mask(maximum_number_of_tails) )
446
447          particle_tail_coordinates  = 0.0
448          minimum_tailpoint_distance = minimum_tailpoint_distance**2
449          number_of_initial_tails    = number_of_tails
450
451          nn = 0
452          DO  n = 1, number_of_particles
453!
454!--          Only for those particles marked above with a provisional tail_id
455!--          tails will be created. Particles now get their final tail_id.
456             IF ( particles(n)%tail_id /= 0 )  THEN
457
458                nn = nn + 1
459                particles(n)%tail_id = nn
460
461                particle_tail_coordinates(1,1,nn) = particles(n)%x
462                particle_tail_coordinates(1,2,nn) = particles(n)%y
463                particle_tail_coordinates(1,3,nn) = particles(n)%z
464                particle_tail_coordinates(1,4,nn) = particles(n)%color
465                particles(n)%tailpoints = 1
466                IF ( minimum_tailpoint_distance /= 0.0 )  THEN
467                   particle_tail_coordinates(2,1,nn) = particles(n)%x
468                   particle_tail_coordinates(2,2,nn) = particles(n)%y
469                   particle_tail_coordinates(2,3,nn) = particles(n)%z
470                   particle_tail_coordinates(2,4,nn) = particles(n)%color
471                   particle_tail_coordinates(1:2,5,nn) = 0.0
472                   particles(n)%tailpoints = 2
473                ENDIF
474
475             ENDIF
476          ENDDO
477       ENDIF
478
479!
480!--    Plot initial positions of particles (only if particle advection is
481!--    switched on from the beginning of the simulation (t=0))
482       IF ( particle_advection_start == 0.0 )  CALL data_output_dvrp
483
484    ENDIF
485
486!
487!-- Check boundary condition and set internal variables
488    SELECT CASE ( bc_par_b )
489   
490       CASE ( 'absorb' )
491          ibc_par_b = 1
492
493       CASE ( 'reflect' )
494          ibc_par_b = 2
495         
496       CASE DEFAULT
497          IF ( myid == 0 )  THEN
498             PRINT*,'+++ init_particles: unknown boundary condition ',   &
499                         'bc_par_b = "', TRIM( bc_par_b ), '"'
500          ENDIF
501          CALL local_stop
502         
503    END SELECT
504    SELECT CASE ( bc_par_t )
505   
506       CASE ( 'absorb' )
507          ibc_par_t = 1
508
509       CASE ( 'reflect' )
510          ibc_par_t = 2
511         
512       CASE DEFAULT
513          IF ( myid == 0 )  THEN
514             PRINT*,'+++ init_particles: unknown boundary condition ',   &
515                         'bc_par_t = "', TRIM( bc_par_t ), '"'
516          ENDIF
517          CALL local_stop
518         
519    END SELECT
520    SELECT CASE ( bc_par_lr )
521
522       CASE ( 'cyclic' )
523          ibc_par_lr = 0
524
525       CASE ( 'absorb' )
526          ibc_par_lr = 1
527
528       CASE ( 'reflect' )
529          ibc_par_lr = 2
530         
531       CASE DEFAULT
532          IF ( myid == 0 )  THEN
533             PRINT*,'+++ init_particles: unknown boundary condition ',   &
534                         'bc_par_lr = "', TRIM( bc_par_lr ), '"'
535          ENDIF
536          CALL local_stop
537         
538    END SELECT
539    SELECT CASE ( bc_par_ns )
540
541       CASE ( 'cyclic' )
542          ibc_par_ns = 0
543
544       CASE ( 'absorb' )
545          ibc_par_ns = 1
546
547       CASE ( 'reflect' )
548          ibc_par_ns = 2
549         
550       CASE DEFAULT
551          IF ( myid == 0 )  THEN
552             PRINT*,'+++ init_particles: unknown boundary condition ',   &
553                         'bc_par_ns = "', TRIM( bc_par_ns ), '"'
554          ENDIF
555          CALL local_stop
556         
557    END SELECT
558!
559!-- Formats
5608000 FORMAT (I6,1X,F7.2,4X,I6,71X,I6)
561
562 END SUBROUTINE init_particles
Note: See TracBrowser for help on using the repository browser.