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/set_slicer_attributes_dvrp.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:
     
    3945#if defined( __dvrp_graphics )
    4046
    41     USE control_parameters
    42     USE dvrp_variables
     47    USE dvrp_variables,                                                        &
     48        ONLY:  dvrp_colortable_entries, interval_h_dvrp, interval_values_dvrp, &
     49               slicer_range_limits_dvrp
     50
     51    USE kinds
    4352
    4453    IMPLICIT NONE
    4554
    46     INTEGER ::  j, n_slicer
    47     REAL    ::  maxv, meav, minv
     55    INTEGER(iwp) ::  j         !:
     56    INTEGER(iwp) ::  n_slicer  !:
     57
     58    REAL(wp)     ::  maxv      !:
     59    REAL(wp)     ::  meav      !:
     60    REAL(wp)     ::  minv      !:
    4861
    4962
Note: See TracChangeset for help on using the changeset viewer.