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

Last change on this file since 212 was 198, checked in by raasch, 16 years ago

file headers updated for the next release 3.5

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