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

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

further adjustments for speedup of particle code

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