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

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

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

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