source: palm/tags/release-3.6/SOURCE/init_particles.f90 @ 701

Last change on this file since 701 was 229, checked in by raasch, 15 years ago

bugfixes concerning particle tails

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