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

Last change on this file since 254 was 254, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

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