source: palm/trunk/SOURCE/lpm_init.f90 @ 978

Last change on this file since 978 was 850, checked in by raasch, 12 years ago

last commit documented

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