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

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

last commit documented

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