source: palm/tags/release-3.4/SOURCE/init_particles.f90 @ 4480

Last change on this file since 4480 was 110, checked in by raasch, 16 years ago

New:
---
Allows runs for a coupled atmosphere-ocean LES,
coupling frequency is controlled by new d3par-parameter dt_coupling,
the coupling mode (atmosphere_to_ocean or ocean_to_atmosphere) for the
respective processes is read from environment variable coupling_mode,
which is set by the mpiexec-command,
communication between the two models is done using the intercommunicator
comm_inter,
local files opened by the ocean model get the additional suffic "_O".
Assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean.

A momentum flux can be set as top boundary condition using the new
inipar parameter top_momentumflux_u|v.

Non-cyclic boundary conditions can be used along all horizontal directions.

Quantities w*p* and w"e can be output as vertical profiles.

Initial profiles are reset to constant profiles in case that initializing_actions /= 'set_constant_profiles'. (init_rankine)

Optionally calculate km and kh from initial TKE e_init.

Changed:


Remaining variables iran changed to iran_part (advec_particles, init_particles).

In case that the presure solver is not called for every Runge-Kutta substep
(call_psolver_at_all_substeps = .F.), it is called after the first substep
instead of the last. In that case, random perturbations are also added to the
velocity field after the first substep.

Initialization of km,kh = 0.00001 for ocean = .T. (for ocean = .F. it remains 0.01).

Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T. (instead of cloud_physics = .T.).

Errors:


Bugs from code parts for non-cyclic boundary conditions are removed: loops for
u and v are starting from index nxlu, nysv, respectively. The radiation boundary
condition is used for every Runge-Kutta substep. Velocity phase speeds for
the radiation boundary conditions are calculated for the first Runge-Kutta
substep only and reused for the further substeps. New arrays c_u, c_v, and c_w
are defined for this purpose. Several index errors are removed from the
radiation boundary condition code parts. Upper bounds for calculating
u_0 and v_0 (in production_e) are nxr+1 and nyn+1 because otherwise these
values are not available in case of non-cyclic boundary conditions.

+dots_num_palm in module user, +module netcdf_control in user_init (both in user_interface)

Bugfix: wrong sign removed from the buoyancy production term in the case use_reference = .T. (production_e)

Bugfix: Error message concerning output of particle concentration (pc) modified (check_parameters).

Bugfix: Rayleigh damping for ocean fixed.

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