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

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

New:
---

Changed:


Optimization of collision kernels. Collision tables can be calculated once at
simulation start for defined radius (and dissipation) classes instead of
re-calculating them at every timestep and for the particle ensemble in
every gridbox.
For this purpose the particle feature color is renamed class.
New parpar parameters radius_classes and dissipation_classes.
(Makefile, advec_particles, check_parameters, data_output_dvrp, header, init_particles, lpm_collision_kernels, modules, package_parin, set_particle_attributes)

Lower limit for droplet radius changed from 1E-7 to 1E-8.
(advec_particles)

Complete re-formatting of collision code (including changes in names of
variables, modules and subroutines).
(advec_particles, lpm_collision_kernels)

Errors:


Bugfix: transformation factor for dissipation changed from 1E5 to 1E4
(advec_particles, lpm_collision_kernels)

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