Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/package_parin.f90

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    3642! replaced by collision_kernel
    3743!
    38 ! 790 2011-11-29 03:11:20Z raasch
    39 ! +turbulence_effects_on_collision, wang_collision_kernel in particles_par
    40 !
    41 ! 336 2009-06-10 11:19:35Z raasch
    42 ! +clip_dvrp_*, cluster_size, color_interval, dvrpsize_interval,
    43 ! groundplate_color, isosurface_color, particle_color, particle_dvrpsize
    44 ! topography_color, in dvrp_graphics_par,
    45 ! parameter dvrp_psize moved from particles_par to dvrp_graphics_par
    46 ! Variables for dvrp-mode pathlines added
    47 !
    48 ! 210 2008-11-06 08:54:02Z raasch
    49 ! Variables for dvrp-mode pathlines added
    50 !
    51 ! 116 2007-10-11 02:30:27Z raasch
    52 ! +dt_sort_particles in package_parin
    53 !
    54 ! 60 2007-03-11 11:50:04Z raasch
    55 ! Particles-package is now part of the default code
    56 !
    57 ! RCS Log replace by Id keyword, revision history cleaned up
    58 !
    59 ! Revision 1.18  2006/08/04 14:52:23  raasch
    60 ! +dt_dopts, dt_min_part, end_time_prel, particles_per_point,
    61 ! use_sgs_for_particles in particles_par
    62 !
    6344! Revision 1.1  2000/12/28 13:21:57  raasch
    6445! Initial revision
     
    7152!------------------------------------------------------------------------------!
    7253
    73     USE control_parameters
    74     USE dvrp_variables
    75     USE particle_attributes
    76     USE spectrum
     54    USE control_parameters,                                                    &
     55        ONLY:  averaging_interval_sp, dt_dopts, dt_dosp, dt_dvrp,              &
     56                particle_maximum_age, skip_time_dosp, threshold
     57
     58    USE dvrp_variables,                                                        &
     59        ONLY:  clip_dvrp_l, clip_dvrp_n, clip_dvrp_r, clip_dvrp_s,             &
     60               cluster_size, color_interval, dvrpsize_interval,                &
     61               dvrp_directory, dvrp_file, dvrp_host, dvrp_output,              &
     62               dvrp_password, dvrp_username, groundplate_color,                &
     63               isosurface_color, mode_dvrp, particle_color,                    &
     64               particle_dvrpsize, pathlines_fadeintime,                        &
     65               pathlines_fadeouttime, pathlines_linecount,                     &
     66               pathlines_maxhistory, pathlines_wavecount,                      &
     67               pathlines_wavetime, slicer_range_limits_dvrp, superelevation,   &
     68               superelevation_x, superelevation_y, topography_color,           &
     69               vc_alpha, vc_gradient_normals, vc_mode, vc_size_x, vc_size_y,   &
     70               vc_size_z
     71
     72    USE particle_attributes,                                                   &
     73        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
     74               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
     75               dt_sort_particles, dt_write_particle_data, dvrp_psize,          &
     76               end_time_prel, initial_weighting_factor,                        &
     77               maximum_number_of_particles, maximum_number_of_tailpoints,      &
     78               maximum_tailpoint_age, minimum_tailpoint_distance,              &
     79               number_of_particle_groups, particles_per_point,                 &
     80               particle_advection, particle_advection_start, pdx, pdy, pdz,    &
     81               psb, psl, psn, psr, pss, pst, radius, radius_classes,           &
     82               random_start_position, read_particles_from_restartfile,         &
     83               skip_particles_for_tail, use_particle_tails,                    &
     84               use_sgs_for_particles, vertical_particle_advection,             &
     85               write_particle_statistics
     86
     87    USE spectrum,                                                              &
     88        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
     89               spectra_direction
    7790
    7891    IMPLICIT NONE
    7992
    80     CHARACTER (LEN=80) ::  zeile
     93    CHARACTER (LEN=80) ::  line  !:
    8194
    8295    NAMELIST /dvrp_graphics_par/  clip_dvrp_l, clip_dvrp_n, clip_dvrp_r,       &
     
    117130                                  vertical_particle_advection,                 &
    118131                                  write_particle_statistics
     132
    119133    NAMELIST /spectra_par/        averaging_interval_sp, comp_spectra_level,   &
    120134                                  data_output_sp, dt_dosp, plot_spectra_level, &
     
    125139!-- parin), search for the namelist-group of the package and position the
    126140!-- file at this line. Do the same for each optionally used package.
    127     zeile = ' '
     141    line = ' '
    128142
    129143#if defined( __dvrp_graphics )
    130144    REWIND ( 11 )
    131     zeile = ' '
    132     DO   WHILE ( INDEX( zeile, '&dvrp_graphics_par' ) == 0 )
    133        READ ( 11, '(A)', END=10 )  zeile
     145    line = ' '
     146    DO   WHILE ( INDEX( line, '&dvrp_graphics_par' ) == 0 )
     147       READ ( 11, '(A)', END=10 )  line
    134148    ENDDO
    135149    BACKSPACE ( 11 )
     
    145159!-- Try to find particles package
    146160    REWIND ( 11 )
    147     zeile = ' '
    148     DO   WHILE ( INDEX( zeile, '&particles_par' ) == 0 )
    149        READ ( 11, '(A)', END=20 )  zeile
     161    line = ' '
     162    DO   WHILE ( INDEX( line, '&particles_par' ) == 0 )
     163       READ ( 11, '(A)', END=20 )  line
    150164    ENDDO
    151165    BACKSPACE ( 11 )
     
    164178#if defined( __spectra )
    165179    REWIND ( 11 )
    166     zeile = ' '
    167     DO   WHILE ( INDEX( zeile, '&spectra_par' ) == 0 )
    168        READ ( 11, '(A)', END=30 )  zeile
     180    line = ' '
     181    DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
     182       READ ( 11, '(A)', END=30 )  line
    169183    ENDDO
    170184    BACKSPACE ( 11 )
Note: See TracChangeset for help on using the changeset viewer.