source: palm/trunk/SOURCE/package_parin.f90 @ 247

Last change on this file since 247 was 242, checked in by raasch, 15 years ago

further additions for clipping - still incomplete

  • Property svn:keywords set to Id
File size: 5.2 KB
Line 
1 SUBROUTINE package_parin
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! +clip_dvrp_*, cluster_size in dvrp_graphics_par
7! Variables for dvrp-mode pathlines added
8!
9! Former revisions:
10! -----------------
11! $Id: package_parin.f90 242 2009-02-23 13:03:18Z heinze $
12!
13! 210 2008-11-06 08:54:02Z raasch
14! Variables for dvrp-mode pathlines added
15!
16! 116 2007-10-11 02:30:27Z raasch
17! +dt_sort_particles in package_parin
18!
19! 60 2007-03-11 11:50:04Z raasch
20! Particles-package is now part of the default code
21!
22! RCS Log replace by Id keyword, revision history cleaned up
23!
24! Revision 1.18  2006/08/04 14:52:23  raasch
25! +dt_dopts, dt_min_part, end_time_prel, particles_per_point,
26! use_sgs_for_particles in particles_par
27!
28! Revision 1.1  2000/12/28 13:21:57  raasch
29! Initial revision
30!
31!
32! Description:
33! ------------
34! This subroutine reads from the NAMELIST file variables controling model
35! software packages which are used optionally in the run.
36!------------------------------------------------------------------------------!
37
38    USE control_parameters
39    USE dvrp_variables
40    USE particle_attributes
41    USE spectrum
42
43    IMPLICIT NONE
44
45    CHARACTER (LEN=80) ::  zeile
46
47    NAMELIST /dvrp_graphics_par/  clip_dvrp_l, clip_dvrp_n, clip_dvrp_r,       &
48                                  clip_dvrp_s, cluster_size, dt_dvrp,          &
49                                  dvrp_directory, dvrp_file, dvrp_host,        &
50                                  dvrp_output, dvrp_password, dvrp_username,   &
51                                  mode_dvrp, pathlines_fadeintime,             &
52                                  pathlines_fadeouttime, pathlines_linecount,  &
53                                  pathlines_maxhistory, pathlines_wavecount,   &
54                                  pathlines_wavetime, slicer_range_limits_dvrp,&
55                                  superelevation, superelevation_x,            &
56                                  superelevation_y, threshold, vc_alpha,       &
57                                  vc_gradient_normals, vc_mode, vc_size_x,     &
58                                  vc_size_y, vc_size_z
59    NAMELIST /particles_par/      bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,    &
60                                  density_ratio, radius, dt_dopts,             &
61                                  dt_min_part, dt_prel, dt_sort_particles,     &
62                                  dt_write_particle_data, dvrp_psize,          &
63                                  end_time_prel, initial_weighting_factor,     &
64                                  maximum_number_of_particles,                 &
65                                  maximum_number_of_tailpoints,                &
66                                  maximum_tailpoint_age,                       &
67                                  minimum_tailpoint_distance,                  &
68                                  number_of_particle_groups,                   &
69                                  particles_per_point,                         &
70                                  particle_advection_start,                    &
71                                  particle_maximum_age, pdx, pdy, pdz, psb,    &
72                                  psl, psn, psr, pss, pst,                     &
73                                  random_start_position,                       &
74                                  read_particles_from_restartfile,             &
75                                  skip_particles_for_tail, use_particle_tails, &
76                                  use_sgs_for_particles,                       &
77                                  vertical_particle_advection,                 &
78                                  write_particle_statistics
79    NAMELIST /spectra_par/        averaging_interval_sp, comp_spectra_level,   &
80                                  data_output_sp, dt_dosp, plot_spectra_level, &
81                                  skip_time_dosp, spectra_direction
82
83!
84!-- Position the namelist-file at the beginning (it was already opened in
85!-- parin), search for the namelist-group of the package and position the
86!-- file at this line. Do the same for each optionally used package.
87    zeile = ' '
88
89#if defined( __dvrp_graphics )
90    REWIND ( 11 )
91    zeile = ' '
92    DO   WHILE ( INDEX( zeile, '&dvrp_graphics_par' ) == 0 )
93       READ ( 11, '(A)', END=10 )  zeile
94    ENDDO
95    BACKSPACE ( 11 )
96
97!
98!-- Read user-defined namelist
99    READ ( 11, dvrp_graphics_par )
100
101 10 CONTINUE
102#endif
103
104!
105!-- Try to find particles package
106    REWIND ( 11 )
107    zeile = ' '
108    DO   WHILE ( INDEX( zeile, '&particles_par' ) == 0 )
109       READ ( 11, '(A)', END=20 )  zeile
110    ENDDO
111    BACKSPACE ( 11 )
112
113!
114!-- Read user-defined namelist
115    READ ( 11, particles_par )
116
117!
118!-- Set flag that indicates that particles are switched on
119    particle_advection = .TRUE.
120
121 20 CONTINUE
122
123
124#if defined( __spectra )
125    REWIND ( 11 )
126    zeile = ' '
127    DO   WHILE ( INDEX( zeile, '&spectra_par' ) == 0 )
128       READ ( 11, '(A)', END=30 )  zeile
129    ENDDO
130    BACKSPACE ( 11 )
131
132!
133!-- Read user-defined namelist
134    READ ( 11, spectra_par )
135
136!
137!-- Default setting of dt_dosp here (instead of check_parameters), because its
138!-- current value is needed in init_pegrid
139    IF ( dt_dosp == 9999999.9 )  dt_dosp = dt_data_output
140
141 30 CONTINUE
142#endif
143
144 END SUBROUTINE package_parin
Note: See TracBrowser for help on using the repository browser.