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/data_output_dvrp.f90

    r1319 r1320  
     1 MODULE dvrp_color
     2
    13!--------------------------------------------------------------------------------!
    24! This file is part of PALM.
     
    1820! Current revisions:
    1921! -----------------
    20 !
     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
    2129!
    2230! Former revisions:
     
    3240! 828 2012-02-21 12:00:36Z raasch
    3341! particle feature color renamed class
    34 !
    35 ! 287 2009-04-09 08:59:36Z raasch
    36 ! Clipping of dvr-output implemented, using a default colourtable for
    37 ! particles,
    38 ! output of messages replaced by message handling routine.
    39 !
    40 ! 210 2008-11-06 08:54:02Z raasch
    41 ! DVRP arguments changed to single precision, mode pathlines added
    42 !
    43 ! 130 2007-11-13 14:08:40Z letzel
    44 ! allow two instead of one digit to specify isosurface and slicer variables
    45 ! for unknown variables (CASE DEFAULT) call new subroutine
    46 ! user_data_output_dvrp
    47 !
    48 ! 82 2007-04-16 15:40:52Z raasch
    49 ! Preprocessor strings for different linux clusters changed to "lc",
    50 ! routine local_flush is used for buffer flushing
    51 !
    52 ! 75 2007-03-22 09:54:05Z raasch
    53 ! Particles-package is now part of the default code,
    54 ! moisture renamed humidity
    55 !
    56 ! RCS Log replace by Id keyword, revision history cleaned up
    57 !
    58 ! Revision 1.13  2006/02/23 10:25:12  raasch
    59 ! Former routine plot_dvrp renamed data_output_dvrp,
    60 ! Only a fraction of the particles may have a tail,
    61 ! pl.. replaced by do.., %size renamed %dvrp_psize
    6242!
    6343! Revision 1.1  2000/04/27 06:27:17  raasch
     
    7050!------------------------------------------------------------------------------!
    7151
    72  MODULE dvrp_color
    73 
    7452    USE dvrp_variables
     53   
     54    USE kinds
    7555
    7656    IMPLICIT NONE
     
    8060    SUBROUTINE color_dvrp( value, color )
    8161
    82        REAL, INTENT(IN)  ::  value
    83        REAL, INTENT(OUT) ::  color(4)
    84 
    85        REAL              ::  scale
    86 
    87        scale = ( value - slicer_range_limits_dvrp(1,islice_dvrp) ) / &
    88                ( slicer_range_limits_dvrp(2,islice_dvrp) -           &
     62       REAL(wp), INTENT(IN)  ::  value    !:
     63       REAL(wp), INTENT(OUT) ::  color(4) !:
     64
     65       REAL(wp)              ::  scale    !:
     66
     67       scale = ( value - slicer_range_limits_dvrp(1,islice_dvrp) ) /           &
     68               ( slicer_range_limits_dvrp(2,islice_dvrp) -                     &
    8969                 slicer_range_limits_dvrp(1,islice_dvrp) )
    9070
    9171       scale = MODULO( 180.0 + 180.0 * scale, 360.0 )
    9272
    93        color = (/ scale, 0.5, 1.0, 0.0 /)
     73       color = (/ scale, 0.5_wp, 1.0_wp, 0.0_wp /)
    9474
    9575    END SUBROUTINE color_dvrp
     
    10282#if defined( __dvrp_graphics )
    10383
    104     USE arrays_3d
    105     USE cloud_parameters
    106     USE constants
    107     USE control_parameters
    108     USE cpulog
     84    USE arrays_3d,                                                             &
     85        ONLY:  p, pt, q, ql, ts, u, us, v, w, zu
     86       
     87    USE cloud_parameters,                                                      &
     88        ONLY:  l_d_cp, pt_d_t
     89       
     90    USE constants,                                                             &
     91        ONLY:  pi
     92       
     93    USE control_parameters,                                                    &
     94        ONLY:  cloud_droplets, cloud_physics, do2d, do3d, humidity, ibc_uv_b,  &
     95               message_string, nz_do3d, passive_scalar, simulated_time,        &
     96               threshold
     97       
     98    USE cpulog,                                                                &
     99        ONLY:  log_point, log_point_s, cpu_log
     100       
    109101    USE DVRP
     102   
    110103    USE dvrp_color
     104       
    111105    USE dvrp_variables
    112     USE grid_variables
    113     USE indices
    114     USE particle_attributes
     106       
     107    USE grid_variables,                                                        &
     108        ONLY:  dx, dy
     109       
     110    USE indices,                                                               &
     111        ONLY:  nxl, nxr, nyn, nys, nzb
     112       
     113    USE kinds
     114   
     115    USE particle_attributes,                                                   &
     116        ONLY:  maximum_number_of_tailpoints, number_of_particles,              &
     117               number_of_tails, particle_advection, particle_advection_start,  &
     118               particle_tail_coordinates, particles, uniform_particles,        &
     119               use_particle_tails
     120       
    115121    USE pegrid
    116122
    117123    IMPLICIT NONE
    118124
    119     CHARACTER (LEN=2) ::  section_chr
    120     CHARACTER (LEN=6) ::  output_variable
    121     INTEGER ::  c_mode, c_size_x, c_size_y, c_size_z, dvrp_nop, dvrp_not,     &
    122                 gradient_normals, i, ip, j, jp, k, l, m, n, n_isosurface,     &
    123                 n_slicer, nn, section_mode, vn
    124     INTEGER, DIMENSION(:), ALLOCATABLE ::  p_c, p_t
    125 
    126     LOGICAL, DIMENSION(:), ALLOCATABLE ::  dvrp_mask
    127 
    128     REAL(4) ::  slicer_position, tmp_alpha, tmp_alpha_w, tmp_b, tmp_c_alpha, &
    129                 tmp_g, tmp_norm, tmp_pos, tmp_r, tmp_t, tmp_th
    130     REAL(4), DIMENSION(:),     ALLOCATABLE   ::  psize, p_x, p_y, p_z
    131     REAL(4), DIMENSION(:,:,:), ALLOCATABLE   ::  local_pf
    132     REAL(4), DIMENSION(:,:,:,:), ALLOCATABLE ::  local_pfi
     125    CHARACTER (LEN=2) ::  section_chr      !:
     126    CHARACTER (LEN=6) ::  output_variable  !:
     127   
     128    INTEGER(iwp) ::  c_mode           !: 
     129    INTEGER(iwp) ::  c_size_x         !:
     130    INTEGER(iwp) ::  c_size_y         !:
     131    INTEGER(iwp) ::  c_size_z         !:
     132    INTEGER(iwp) ::  dvrp_nop         !:
     133    INTEGER(iwp) ::  dvrp_not         !:
     134    INTEGER(iwp) ::  gradient_normals !:
     135    INTEGER(iwp) ::  i                !:
     136    INTEGER(iwp) ::  ip               !:
     137    INTEGER(iwp) ::  j                !:
     138    INTEGER(iwp) ::  jp               !:
     139    INTEGER(iwp) ::  k                !:
     140    INTEGER(iwp) ::  l                !:
     141    INTEGER(iwp) ::  m                !:
     142    INTEGER(iwp) ::  n                !:
     143    INTEGER(iwp) ::  n_isosurface     !:
     144    INTEGER(iwp) ::  n_slicer         !:
     145    INTEGER(iwp) ::  nn               !:
     146    INTEGER(iwp) ::  section_mode     !:
     147    INTEGER(iwp) ::  vn               !:
     148    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  p_c  !:
     149    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  p_t  !:
     150
     151    LOGICAL, DIMENSION(:), ALLOCATABLE ::  dvrp_mask  !:
     152
     153    REAL(sp) ::  slicer_position  !:
     154    REAL(sp) ::  tmp_alpha        !:
     155    REAL(sp) ::  tmp_alpha_w      !:
     156    REAL(sp) ::  tmp_b            !:
     157    REAL(sp) ::  tmp_c_alpha      !:
     158    REAL(sp) ::  tmp_g            !:
     159    REAL(sp) ::  tmp_norm         !:
     160    REAL(sp) ::  tmp_pos          !:
     161    REAL(sp) ::  tmp_r            !:
     162    REAL(sp) ::  tmp_t            !:
     163    REAL(sp) ::  tmp_th           !:
     164    REAL(sp), DIMENSION(:),     ALLOCATABLE   ::  psize  !:
     165    REAL(sp), DIMENSION(:),     ALLOCATABLE   ::  p_x    !:
     166    REAL(sp), DIMENSION(:),     ALLOCATABLE   ::  p_y    !:
     167    REAL(sp), DIMENSION(:),     ALLOCATABLE   ::  p_z    !:
     168    REAL(sp), DIMENSION(:,:,:), ALLOCATABLE   ::  local_pf  !:
     169    REAL(sp), DIMENSION(:,:,:,:), ALLOCATABLE ::  local_pfi !:
    133170
    134171
Note: See TracChangeset for help on using the changeset viewer.