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_3d.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! revision history before 2012 removed,
     25! comment fields (!:) to be used for variable explanations added to
     26! all variable declaration statements
    2327!
    2428! Former revisions:
     
    3236! code put under GPL (PALM 3.9)
    3337!
    34 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    35 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    36 !
    3738! 211 2008-11-11 04:46:24Z raasch
    3839! Former file user_interface.f90 split into one file per subroutine
     
    4546
    4647    USE indices
    47     USE precision_kind
     48
     49    USE kinds
     50
    4851    USE user
    4952
    5053    IMPLICIT NONE
    5154
    52     CHARACTER (LEN=*) ::  variable
     55    CHARACTER (LEN=*) ::  variable !:
    5356
    54     INTEGER ::  av, i, j, k, nz_do
     57    INTEGER(iwp) ::  av    !:
     58    INTEGER(iwp) ::  i     !:
     59    INTEGER(iwp) ::  j     !:
     60    INTEGER(iwp) ::  k     !:
     61    INTEGER(iwp) ::  nz_do !:
    5562
    56     LOGICAL ::  found
     63    LOGICAL      ::  found !:
    5764
    58    REAL(spk), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nz_do) ::  local_pf
     65   REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nz_do) ::  local_pf !:
    5966
    6067
Note: See TracChangeset for help on using the changeset viewer.