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_3d_data_averaging.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:
     
    3943
    4044    USE control_parameters
     45
    4146    USE indices
     47
     48    USE kinds
     49
    4250    USE user
    4351
    4452    IMPLICIT NONE
    4553
    46     CHARACTER (LEN=*) ::  mode, variable
     54    CHARACTER (LEN=*) ::  mode    !:
     55    CHARACTER (LEN=*) :: variable !:
    4756
    48     INTEGER ::  i, j, k
    49 
     57    INTEGER(iwp) ::  i !:
     58    INTEGER(iwp) ::  j !:
     59    INTEGER(iwp) ::  k !:
    5060
    5161    IF ( mode == 'allocate' )  THEN
Note: See TracChangeset for help on using the changeset viewer.