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

Last change on this file since 337 was 336, checked in by raasch, 15 years ago

several small bugfixes; some more dvrp changes

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