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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 24.0 KB
Line 
1 SUBROUTINE init_particles
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: init_particles.f90,v $
11! Revision 1.24  2007/02/11 13:00:17  raasch
12! Bugfix: allocation of tail_mask and new_tail_id in case of restart-runs
13! Bugfix: __ was missing in a cpp-directive
14!
15! Revision 1.23  2006/08/22 14:11:08  raasch
16! Default settings of particle start positions changed
17!
18! Revision 1.22  2006/08/04 14:44:58  raasch
19! New particles attributes initialized (e_m, dt_sum, speed_x/y/z_sgs),
20! total length of mpi_particle_type adjusted, more than one particle can be
21! released per point, izuf renamed iran, set a special seed value iran_part
22! to be used for the particle advection code, determination of particle group
23! number removed from header to here
24!
25! Revision 1.21  2006/03/14 12:55:24  raasch
26! Determination of the number of particle groups removed
27!
28! Revision 1.20  2006/02/23 12:34:00  raasch
29! Allocation of prt_start_index and prt_count + calling subroutine
30! sort_particles,
31! particle source parameters psl, psr, pss, psn, psb, pst, pdx, pdy, pdz are now
32! 1D arrays (1:max_number_of_particle_groups) and allow up to specify
33! max_number_of_particle_groups different sources by setting
34! number_of_particle_groups >= 1 even if density_ratio is not specified,
35! only a fraction of the particles may have tails, therefore input from unit 90
36! has changed,
37! 0.5 replaced by 0.4999999999 in setting the random fluctuations,
38! Defaults of psl, psr, pss, psn adjusted.
39! If the number of particle groups is set by the user, density_ratio is reset to
40! default.
41! In case of user-specified pdx, pdy, pdz = 0.0 reset them to defaults,
42! improve particle release at PE boundaries, nt_anz renamed
43! current_timestep_number
44!
45! Revision 1.19  2005/06/26 19:56:47  raasch
46! particle_groups%radius is used instead of diameter, particle%radius is
47! initialized, new initial informations about radius and weighting factor
48! stored on array particles, total length of mpi_particle_type adjusted
49!
50! Revision 1.18  2004/04/30 12:03:28  raasch
51! MPI data type for particles modified due to modification of FORTRAN particle
52! type
53!
54! Revision 1.17  2003/10/29 08:55:35  raasch
55! Module random_function_mod is used, version check of the binary file,
56! modifications for new particle group feature
57!
58! Revision 1.16  2003/03/16 09:39:51  raasch
59! Two underscores (_) are placed in front of all define-strings
60!
61! Revision 1.15  2003/03/04 11:30:48  raasch
62! Displacement for integers in mpi_particle_type reduced from 16 to 8 on
63! ibm, since integers seem to be only 4 byte long. Accordingly, total length
64! reduced from 104 to 96.
65!
66! Revision 1.14  2002/12/19 15:39:48  raasch
67! STOP statement replaced by call of subroutine local_stop
68!
69! Revision 1.13  2002/09/12 13:04:13  raasch
70! Read density_ratio from restart file
71!
72! Revision 1.12  2002/04/16 08:08:34  raasch
73! New initial informations about speed components and start positions stored on
74! array particles. Check boundary conditions and read them from restart file.
75!
76! Revision 1.11  2001/11/12 16:06:06  raasch
77! Array particle_tail_coordinates extended to contain colour informations,
78! reading particle data from restart file can be prohibited
79!
80! Revision 1.9  2001/08/21 09:49:05  raasch
81! Particle tail is initialized
82!
83! Revision 1.8  2001/07/12 12:10:58  raasch
84! Particle sources (starting positions) are now controlled by parameters
85!
86! Revision 1.7  2001/03/30 07:31:37  raasch
87! Translation of remaining German identifiers (variables, subroutines, etc.)
88!
89! Revision 1.6  2001/01/25 07:05:36  raasch
90! Writing of particle informations is optional now
91!
92! Revision 1.5  2001/01/22 07:16:17  raasch
93! Module test_particles removed
94!
95! Revision 1.4  2001/01/02 17:30:16  raasch
96! Opening of unit 80 moved to check_open. Unit 90 instead of 81 is used
97! for binary input.
98!
99! Revision 1.3  2000/12/28 13:15:58  raasch
100! Complete revision due to new features of dvrp-software,
101! all comments translated into English,
102! code is used only optionally (cpp-directives are added)
103!
104! Revision 1.2  2000/04/27 06:38:48  raasch
105! compute position of camera with new indepent routine vtk_camera and
106! store result on a separate file
107!
108! Revision 1.1  1999/11/25 16:22:38  raasch
109! Initial revision
110!
111!
112! Description:
113! ------------
114! This routine initializes a set of particles and their attributes (position,
115! radius, ..). Advection of these particles is carried out by advec_particles,
116! plotting is done in data_output_dvrp.
117!------------------------------------------------------------------------------!
118#if defined( __particles )
119
120    USE arrays_3d
121    USE control_parameters
122    USE grid_variables
123    USE indices
124    USE particle_attributes
125    USE pegrid
126    USE random_function_mod
127
128
129    IMPLICIT NONE
130
131    CHARACTER (LEN=10) ::  particle_binary_version, version_on_file
132
133    INTEGER ::  i, j, n, nn
134#if defined( __parallel )
135    INTEGER, DIMENSION(3) ::  blocklengths, displacements, types
136#endif
137    LOGICAL ::  uniform_particles_l
138    REAL    ::  factor, pos_x, pos_y, pos_z, value
139
140
141#if defined( __parallel )
142!
143!-- Define MPI derived datatype for FORTRAN datatype particle_type (see module
144!-- particle_attributes). Integer length is 4 byte, Real is 8 byte (=> total
145!-- length 100, nevertheless, 120 bytes are needed on T3E since integer seems
146!-- to be 8 bytes long there)
147    blocklengths(1)  = 18; blocklengths(2)  = 4; blocklengths(3)  =  1
148#if defined( __t3eb )
149    displacements(1) = 0; displacements(2) = 144; displacements(3) = 176
150#else
151    displacements(1) = 0; displacements(2) = 144; displacements(3) = 160
152#endif
153    types(1) = MPI_REAL
154    types(2) = MPI_INTEGER
155    types(3) = MPI_UB
156    CALL MPI_TYPE_STRUCT( 3, blocklengths, displacements, types, &
157                          mpi_particle_type, ierr )
158    CALL MPI_TYPE_COMMIT( mpi_particle_type, ierr )
159#endif
160
161!
162!-- Check the number of particle groups.
163    IF ( number_of_particle_groups > max_number_of_particle_groups )  THEN
164       PRINT*, '+++ WARNING: init_particles: ', &
165                    'max_number_of_particle_groups =', &
166               max_number_of_particle_groups
167       PRINT*, '+++          number_of_particle_groups reset to ', &
168               max_number_of_particle_groups
169       number_of_particle_groups = max_number_of_particle_groups
170    ENDIF
171
172!
173!-- Set default start positions, if necessary
174    IF ( psl(1) == 9999999.9 )  psl(1) = -0.5 * dx
175    IF ( psr(1) == 9999999.9 )  psr(1) = ( nx + 0.5 ) * dx
176    IF ( pss(1) == 9999999.9 )  pss(1) = -0.5 * dy
177    IF ( psn(1) == 9999999.9 )  psn(1) = ( ny + 0.5 ) * dy
178    IF ( psb(1) == 9999999.9 )  psb(1) = zu(nz/2)
179    IF ( pst(1) == 9999999.9 )  pst(1) = psb(1)
180
181    IF ( pdx(1) == 9999999.9  .OR.  pdx(1) == 0.0 )  pdx(1) = dx
182    IF ( pdy(1) == 9999999.9  .OR.  pdy(1) == 0.0 )  pdy(1) = dy
183    IF ( pdz(1) == 9999999.9  .OR.  pdz(1) == 0.0 )  pdz(1) = zu(2) - zu(1)
184
185    DO  j = 2, number_of_particle_groups
186       IF ( psl(j) == 9999999.9 )  psl(j) = psl(j-1)
187       IF ( psr(j) == 9999999.9 )  psr(j) = psr(j-1)
188       IF ( pss(j) == 9999999.9 )  pss(j) = pss(j-1)
189       IF ( psn(j) == 9999999.9 )  psn(j) = psn(j-1)
190       IF ( psb(j) == 9999999.9 )  psb(j) = psb(j-1)
191       IF ( pst(j) == 9999999.9 )  pst(j) = pst(j-1)
192       IF ( pdx(j) == 9999999.9  .OR.  pdx(j) == 0.0 )  pdx(j) = pdx(j-1)
193       IF ( pdy(j) == 9999999.9  .OR.  pdy(j) == 0.0 )  pdy(j) = pdy(j-1)
194       IF ( pdz(j) == 9999999.9  .OR.  pdz(j) == 0.0 )  pdz(j) = pdz(j-1)
195    ENDDO
196
197!
198!-- For the first model run of a possible job chain initialize the
199!-- particles, otherwise read the particle data from file.
200    IF ( TRIM( initializing_actions ) == 'read_restart_data'  &
201         .AND.  read_particles_from_restartfile )  THEN
202
203!
204!--    Read particle data from previous model run.
205!--    First open the input unit.
206       IF ( myid_char == '' )  THEN
207          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char, &
208                     FORM='UNFORMATTED' )
209       ELSE
210          OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char, &
211                     FORM='UNFORMATTED' )
212       ENDIF
213
214!
215!--    First compare the version numbers
216       READ ( 90 )  version_on_file
217       particle_binary_version = '3.0'
218       IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
219          IF ( myid == 0 )  THEN
220             PRINT*, '+++ init_particles: version mismatch concerning data ', &
221                     'from prior run'
222             PRINT*, '        version on file    = "', TRIM( version_on_file ),&
223                     '"'
224             PRINT*, '        version in program = "', &
225                     TRIM( particle_binary_version ), '"'
226          ENDIF
227          CALL local_stop
228       ENDIF
229
230!
231!--    Read some particle parameters and the size of the particle arrays,
232!--    allocate them and read their contents.
233       READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                  &
234                    maximum_number_of_particles, maximum_number_of_tailpoints, &
235                    maximum_number_of_tails, number_of_initial_particles,      &
236                    number_of_particles, number_of_particle_groups,            &
237                    number_of_tails, particle_groups, time_prel,               &
238                    time_write_particle_data, uniform_particles
239
240       IF ( number_of_initial_particles /= 0 )  THEN
241          ALLOCATE( initial_particles(1:number_of_initial_particles) )
242          READ ( 90 )  initial_particles
243       ENDIF
244
245       ALLOCATE( prt_count(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),       &
246                 prt_start_index(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
247                 particle_mask(maximum_number_of_particles),         &
248                 particles(maximum_number_of_particles) )
249
250       READ ( 90 )  prt_count, prt_start_index
251       READ ( 90 )  particles
252
253       IF ( use_particle_tails )  THEN
254          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
255                    maximum_number_of_tails),                                 &
256                    new_tail_id(maximum_number_of_tails),                     &
257                    tail_mask(maximum_number_of_tails) )
258          READ ( 90 )  particle_tail_coordinates
259       ENDIF
260
261       CLOSE ( 90 )
262
263    ELSE
264
265!
266!--    Allocate particle arrays and set attributes of the initial set of
267!--    particles, which can be also periodically released at later times.
268!--    Also allocate array for particle tail coordinates, if needed.
269       ALLOCATE( prt_count(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),       &
270                 prt_start_index(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
271                 particle_mask(maximum_number_of_particles),         &
272                 particles(maximum_number_of_particles) )
273
274!
275!--    Initialize all particles with dummy values (otherwise errors may
276!--    occur within restart runs). The reason for this is still not clear
277!--    and may be presumably caused by errors in the respective user-interface.
278       particles = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
279                                  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
280                                  0, 0, 0, 0 )
281       particle_groups = particle_groups_type( 0.0, 0.0, 0.0, 0.0 )
282
283!
284!--    Set the default particle size used for dvrp plots
285       IF ( dvrp_psize == 9999999.9 )  dvrp_psize = 0.2 * dx
286
287!
288!--    Set values for the density ratio and radius for all particle
289!--    groups, if necessary
290       IF ( density_ratio(1) == 9999999.9 )  density_ratio(1) = 0.0
291       IF ( radius(1)        == 9999999.9 )  radius(1) = 0.0
292       DO  i = 2, number_of_particle_groups
293          IF ( density_ratio(i) == 9999999.9 )  THEN
294             density_ratio(i) = density_ratio(i-1)
295          ENDIF
296          IF ( radius(i) == 9999999.9 )  radius(i) = radius(i-1)
297       ENDDO
298
299       DO  i = 1, number_of_particle_groups
300          IF ( density_ratio(i) /= 0.0  .AND.  radius(i) == 0 )  THEN
301             IF ( myid == 0 )  THEN
302                PRINT*, '+++ init_particles: particle group #', i, 'has a', &
303                        'density ratio /= 0 but radius = 0'
304             ENDIF
305             CALL local_stop
306          ENDIF
307          particle_groups(i)%density_ratio = density_ratio(i)
308          particle_groups(i)%radius        = radius(i)
309       ENDDO
310
311!
312!--    Calculate particle positions and store particle attributes, if
313!--    particle is situated on this PE
314       n = 0
315
316       DO  i = 1, number_of_particle_groups
317
318          pos_z = psb(i)
319
320          DO WHILE ( pos_z <= pst(i) )
321
322             pos_y = pss(i)
323
324             DO WHILE ( pos_y <= psn(i) )
325
326                IF ( pos_y >= ( nys - 0.5 ) * dy  .AND.  &
327                     pos_y <  ( nyn + 0.5 ) * dy )  THEN
328
329                   pos_x = psl(i)
330
331                   DO WHILE ( pos_x <= psr(i) )
332
333                      IF ( pos_x >= ( nxl - 0.5 ) * dx  .AND.  &
334                           pos_x <  ( nxr + 0.5 ) * dx )  THEN
335
336                         DO  j = 1, particles_per_point
337
338                            n = n + 1
339                            IF ( n > maximum_number_of_particles )  THEN
340                               PRINT*,'+++ init_particles: number of initial', &
341                                      ' particles (', n, ') exceeds'
342                               PRINT*,'    maximum_number_of_particles (',     &
343                                      maximum_number_of_particles, ') on PE ', &
344                                      myid
345#if defined( __parallel )
346                               CALL MPI_ABORT( comm2d, 9999, ierr )
347#else
348                               CALL local_stop
349#endif
350                            ENDIF
351                            particles(n)%x             = pos_x
352                            particles(n)%y             = pos_y
353                            particles(n)%z             = pos_z
354                            particles(n)%age           = 0.0
355                            particles(n)%dt_sum        = 0.0
356                            particles(n)%dvrp_psize    = dvrp_psize
357                            particles(n)%e_m           = 0.0
358                            particles(n)%speed_x       = 0.0
359                            particles(n)%speed_x_sgs   = 0.0
360                            particles(n)%speed_y       = 0.0
361                            particles(n)%speed_y_sgs   = 0.0
362                            particles(n)%speed_z       = 0.0
363                            particles(n)%speed_z_sgs   = 0.0
364                            particles(n)%origin_x      = pos_x
365                            particles(n)%origin_y      = pos_y
366                            particles(n)%origin_z      = pos_z
367                            particles(n)%radius      = particle_groups(i)%radius
368                            particles(n)%weight_factor =initial_weighting_factor
369                            particles(n)%color         = 1
370                            particles(n)%group         = i
371                            particles(n)%tailpoints    = 0
372                            IF ( use_particle_tails  .AND. &
373                                 MOD( n, skip_particles_for_tail ) == 0 )  THEN
374                               number_of_tails         = number_of_tails + 1
375!
376!--                            This is a temporary provisional setting (see
377!--                            further below!)
378                               particles(n)%tail_id    = number_of_tails
379                            ELSE
380                               particles(n)%tail_id    = 0
381                            ENDIF
382
383                         ENDDO
384
385                      ENDIF
386
387                      pos_x = pos_x + pdx(i)
388
389                   ENDDO
390
391                ENDIF
392
393                pos_y = pos_y + pdy(i)
394
395             ENDDO
396
397             pos_z = pos_z + pdz(i)
398
399          ENDDO
400
401       ENDDO
402
403       number_of_initial_particles = n
404       number_of_particles         = n
405
406!
407!--    Calculate the number of particles and tails of the total domain
408#if defined( __parallel )
409       CALL MPI_ALLREDUCE( number_of_particles, total_number_of_particles, 1, &
410                           MPI_REAL, MPI_SUM, comm2d, ierr )
411       CALL MPI_ALLREDUCE( number_of_tails, total_number_of_tails, 1, &
412                           MPI_REAL, MPI_SUM, comm2d, ierr )
413#else
414       total_number_of_particles = number_of_particles
415       total_number_of_tails     = number_of_tails
416#endif
417
418!
419!--    Set a seed value for the random number generator to be exclusively
420!--    used for the particle code. The generated random numbers should be
421!--    different on the different PEs.
422       iran_part = iran_part + myid
423
424!
425!--    User modification of initial particles
426       CALL user_init_particles
427
428!
429!--    Store the initial set of particles for release at later times
430       IF ( number_of_initial_particles /= 0 )  THEN
431          ALLOCATE( initial_particles(1:number_of_initial_particles) )
432          initial_particles(1:number_of_initial_particles) = &
433                                        particles(1:number_of_initial_particles)
434       ENDIF
435
436!
437!--    Add random fluctuation to particle positions
438       IF ( random_start_position )  THEN
439
440          iran = iran + myid    ! Random positions should be different on
441                                ! different PEs
442
443          DO  n = 1, number_of_initial_particles
444             IF ( psl(particles(n)%group) /= psr(particles(n)%group) )  THEN
445                particles(n)%x = particles(n)%x + &
446                                 ( random_function( iran ) - 0.5 ) * &
447                                 pdx(particles(n)%group)
448                IF ( particles(n)%x  <=  ( nxl - 0.5 ) * dx )  THEN
449                   particles(n)%x = ( nxl - 0.4999999999 ) * dx
450                ELSEIF ( particles(n)%x  >=  ( nxr + 0.5 ) * dx )  THEN
451                   particles(n)%x = ( nxr + 0.4999999999 ) * dx
452                ENDIF
453             ENDIF
454             IF ( pss(particles(n)%group) /= psn(particles(n)%group) )  THEN
455                particles(n)%y = particles(n)%y + &
456                                 ( random_function( iran ) - 0.5 ) * &
457                                 pdy(particles(n)%group)
458                IF ( particles(n)%y  <=  ( nys - 0.5 ) * dy )  THEN
459                   particles(n)%y = ( nys - 0.4999999999 ) * dy
460                ELSEIF ( particles(n)%y  >=  ( nyn + 0.5 ) * dy )  THEN
461                   particles(n)%y = ( nyn + 0.4999999999 ) * dy
462                ENDIF
463             ENDIF
464             IF ( psb(particles(n)%group) /= pst(particles(n)%group) )  THEN
465                particles(n)%z = particles(n)%z + &
466                                 ( random_function( iran ) - 0.5 ) * &
467                                 pdz(particles(n)%group)
468             ENDIF
469          ENDDO
470       ENDIF
471
472!
473!--    Sort particles in the sequence the gridboxes are stored in the memory
474       CALL sort_particles
475
476!
477!--    Open file for statistical informations about particle conditions
478       IF ( write_particle_statistics )  THEN
479          CALL check_open( 80 )
480          WRITE ( 80, 8000 )  current_timestep_number, simulated_time, &
481                              number_of_initial_particles,             &
482                              maximum_number_of_particles
483          CALL close_file( 80 )
484       ENDIF
485
486!
487!--    Check if particles are really uniform in color and radius (dvrp_size)
488!--    (uniform_particles is preset TRUE)
489       IF ( uniform_particles )  THEN
490          IF ( number_of_initial_particles == 0 )  THEN
491             uniform_particles_l = .TRUE.
492          ELSE
493             n = number_of_initial_particles
494             IF ( MINVAL( particles(1:n)%dvrp_psize  ) ==     &
495                  MAXVAL( particles(1:n)%dvrp_psize  )  .AND. &
496                  MINVAL( particles(1:n)%color ) ==     &
497                  MAXVAL( particles(1:n)%color ) )  THEN
498                uniform_particles_l = .TRUE.
499             ELSE
500                uniform_particles_l = .FALSE.
501             ENDIF
502          ENDIF
503
504#if defined( __parallel )
505          CALL MPI_ALLREDUCE( uniform_particles_l, uniform_particles, 1, &
506                              MPI_LOGICAL, MPI_LAND, comm2d, ierr )
507#else
508          uniform_particles = uniform_particles_l
509#endif
510
511       ENDIF
512
513!
514!--    Set the beginning of the particle tails and their age
515       IF ( use_particle_tails )  THEN
516!
517!--       Choose the maximum number of tails significantly larger than the
518!--       one initially required
519          factor = 10.0
520          value  = number_of_tails
521          DO WHILE ( value / 10.0 >= 1.0 )
522             factor = factor * 10.0
523             value  = value / 10.0
524          ENDDO
525          maximum_number_of_tails = factor * INT( value )
526
527          ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
528                    maximum_number_of_tails),                                 &
529                    new_tail_id(maximum_number_of_tails),                     &
530                    tail_mask(maximum_number_of_tails) )
531
532          particle_tail_coordinates  = 0.0
533          minimum_tailpoint_distance = minimum_tailpoint_distance**2
534          number_of_initial_tails    = number_of_tails
535
536          nn = 0
537          DO  n = 1, number_of_particles
538!
539!--          Only for those particles marked above with a provisional tail_id
540!--          tails will be created. Particles now get their final tail_id.
541             IF ( particles(n)%tail_id /= 0 )  THEN
542
543                nn = nn + 1
544                particles(n)%tail_id = nn
545
546                particle_tail_coordinates(1,1,nn) = particles(n)%x
547                particle_tail_coordinates(1,2,nn) = particles(n)%y
548                particle_tail_coordinates(1,3,nn) = particles(n)%z
549                particle_tail_coordinates(1,4,nn) = particles(n)%color
550                particles(n)%tailpoints = 1
551                IF ( minimum_tailpoint_distance /= 0.0 )  THEN
552                   particle_tail_coordinates(2,1,nn) = particles(n)%x
553                   particle_tail_coordinates(2,2,nn) = particles(n)%y
554                   particle_tail_coordinates(2,3,nn) = particles(n)%z
555                   particle_tail_coordinates(2,4,nn) = particles(n)%color
556                   particle_tail_coordinates(1:2,5,nn) = 0.0
557                   particles(n)%tailpoints = 2
558                ENDIF
559
560             ENDIF
561          ENDDO
562       ENDIF
563
564!
565!--    Plot initial positions of particles (only if particle advection is
566!--    switched on from the beginning of the simulation (t=0))
567       IF ( particle_advection_start == 0.0 )  CALL data_output_dvrp
568
569    ENDIF
570
571!
572!-- Check boundary condition and set internal variables
573    SELECT CASE ( bc_par_b )
574   
575       CASE ( 'absorb' )
576          ibc_par_b = 1
577
578       CASE ( 'reflect' )
579          ibc_par_b = 2
580         
581       CASE DEFAULT
582          IF ( myid == 0 )  THEN
583             PRINT*,'+++ init_particles: unknown boundary condition ',   &
584                         'bc_par_b = "', TRIM( bc_par_b ), '"'
585          ENDIF
586          CALL local_stop
587         
588    END SELECT
589    SELECT CASE ( bc_par_t )
590   
591       CASE ( 'absorb' )
592          ibc_par_t = 1
593
594       CASE ( 'reflect' )
595          ibc_par_t = 2
596         
597       CASE DEFAULT
598          IF ( myid == 0 )  THEN
599             PRINT*,'+++ init_particles: unknown boundary condition ',   &
600                         'bc_par_t = "', TRIM( bc_par_t ), '"'
601          ENDIF
602          CALL local_stop
603         
604    END SELECT
605    SELECT CASE ( bc_par_lr )
606
607       CASE ( 'cyclic' )
608          ibc_par_lr = 0
609
610       CASE ( 'absorb' )
611          ibc_par_lr = 1
612
613       CASE ( 'reflect' )
614          ibc_par_lr = 2
615         
616       CASE DEFAULT
617          IF ( myid == 0 )  THEN
618             PRINT*,'+++ init_particles: unknown boundary condition ',   &
619                         'bc_par_lr = "', TRIM( bc_par_lr ), '"'
620          ENDIF
621          CALL local_stop
622         
623    END SELECT
624    SELECT CASE ( bc_par_ns )
625
626       CASE ( 'cyclic' )
627          ibc_par_ns = 0
628
629       CASE ( 'absorb' )
630          ibc_par_ns = 1
631
632       CASE ( 'reflect' )
633          ibc_par_ns = 2
634         
635       CASE DEFAULT
636          IF ( myid == 0 )  THEN
637             PRINT*,'+++ init_particles: unknown boundary condition ',   &
638                         'bc_par_ns = "', TRIM( bc_par_ns ), '"'
639          ENDIF
640          CALL local_stop
641         
642    END SELECT
643!
644!-- Formats
6458000 FORMAT (I6,1X,F7.2,4X,I6,71X,I6)
646
647#endif
648 END SUBROUTINE init_particles
Note: See TracBrowser for help on using the repository browser.