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

Last change on this file since 183 was 150, checked in by raasch, 16 years ago

particle advection allowed for ocean runs

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