source: palm/trunk/SOURCE/lpm_init.f90 @ 1319

Last change on this file since 1319 was 1315, checked in by suehring, 10 years ago

last commit documented

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