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

    r1319 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! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    3742! 828 2012-02-21 12:00:36Z raasch
    3843! particle feature color renamed class
    39 !
    40 ! 622 2010-12-10 08:08:13Z raasch
    41 ! optional barriers included in order to speed up collective operations
    4244!
    4345! 271 2009-03-26 00:47:14Z raasch
     
    5052!------------------------------------------------------------------------------!
    5153
    52     USE arrays_3d
    53     USE control_parameters
    54     USE cpulog
    55     USE dvrp_variables
    56     USE grid_variables
    57     USE indices
    58     USE particle_attributes
     54    USE arrays_3d,                                                             &
     55        ONLY:  pt, u, v, w, zu, zw
     56
     57    USE control_parameters,                                                    &
     58        ONLY:  atmos_ocean_sign, u_gtrans, v_gtrans, dz
     59
     60    USE cpulog,                                                                &
     61        ONLY:  cpu_log, log_point_s
     62
     63    USE dvrp_variables,                                                        &
     64        ONLY:  color_interval, dvrp_colortable_entries_prt, dvrpsize_interval, &
     65               particle_color, particle_dvrpsize
     66
     67    USE grid_variables,                                                        &
     68        ONLY:  ddx, dx, ddy, dy
     69
     70    USE indices,                                                               &
     71        ONLY:  ngp_2dh, nxl, nxr, nyn, nys, nzb, nzt
     72
     73    USE kinds
     74
     75    USE particle_attributes,                                                   &
     76        ONLY:  number_of_particles, offset_ocean_nzt, particles
     77
    5978    USE pegrid
    60     USE statistics
     79
     80    USE statistics,                                                            &
     81        ONLY:  sums, sums_l
    6182
    6283    IMPLICIT NONE
    6384
    64     INTEGER ::  i, j, k, n
    65     REAL    ::  aa, absuv, bb, cc, dd, gg, height, pt_int, pt_int_l, pt_int_u, &
    66                 u_int, u_int_l, u_int_u, v_int, v_int_l, v_int_u, w_int,       &
    67                 w_int_l, w_int_u, x, y
    68 
     85    INTEGER(iwp) ::  i        !:
     86    INTEGER(iwp) ::  j        !:
     87    INTEGER(iwp) ::  k        !:
     88    INTEGER(iwp) ::  n        !:
     89
     90    REAL(wp)    ::  aa        !:
     91    REAL(wp)    ::  absuv     !:
     92    REAL(wp)    ::  bb        !:
     93    REAL(wp)    ::  cc        !:
     94    REAL(wp)    ::  dd        !:
     95    REAL(wp)    ::  gg        !:
     96    REAL(wp)    ::  height    !:
     97    REAL(wp)    ::  pt_int    !:
     98    REAL(wp)    ::  pt_int_l  !:
     99    REAL(wp)    ::  pt_int_u  !:
     100    REAL(wp)    ::  u_int     !:
     101    REAL(wp)    ::  u_int_l   !:
     102    REAL(wp)    ::  u_int_u   !:
     103    REAL(wp)    ::  v_int     !:
     104    REAL(wp)    ::  v_int_l   !:
     105    REAL(wp)    ::  v_int_u   !:
     106    REAL(wp)    ::  w_int     !:
     107    REAL(wp)    ::  w_int_l   !:
     108    REAL(wp)    ::  w_int_u   !:
     109    REAL(wp)    ::  x         !:
     110    REAL(wp)    ::  y         !:
    69111
    70112    CALL cpu_log( log_point_s(49), 'lpm_set_attributes', 'start' )
Note: See TracChangeset for help on using the changeset viewer.