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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! kind-parameters added to all INTEGER and REAL declaration statements,
     23! kinds are defined in new module kinds,
     24! old module precision_kind is removed,
     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:
     
    2833! 1036 2012-10-22 13:43:42Z raasch
    2934! code put under GPL (PALM 3.9)
    30 !
    31 ! 258 2009-03-13 12:36:03Z heinze
    32 ! Output of messages replaced by message handling routine.
    33 ! Clipping implemented
    3435!
    3536! 211 2008-11-11 04:46:24Z raasch
     
    4243
    4344    USE control_parameters
     45
    4446    USE dvrp_variables
     47
    4548    USE indices
     49
     50    USE kinds
     51
    4652    USE pegrid
     53
    4754    USE user
    4855
    4956    IMPLICIT NONE
    5057
    51     CHARACTER (LEN=*) ::  output_variable
     58    CHARACTER (LEN=*) ::  output_variable !:
    5259
    53     INTEGER ::  i, j, k
     60    INTEGER(iwp) ::  i !:
     61    INTEGER(iwp) ::  j !:
     62    INTEGER(iwp) ::  k !:
    5463
    55     REAL, DIMENSION(nxl_dvrp:nxr_dvrp+1,nys_dvrp:nyn_dvrp+1,nzb:nz_do3d) :: &
    56                                                                        local_pf
     64    REAL(wp), DIMENSION(nxl_dvrp:nxr_dvrp+1,nys_dvrp:nyn_dvrp+1,nzb:nz_do3d) :: &
     65              local_pf !:
    5766
    5867!
Note: See TracChangeset for help on using the changeset viewer.