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_log.f90

    r1310 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! 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
    2329!
    2430! Former revisions:
     
    4147#if defined( __logging )
    4248
    43     USE control_parameters
     49    USE control_parameters,                                                    &
     50        ONLY:  log_message, simulated_time
     51       
     52    USE kinds
     53       
    4454    USE pegrid
    4555
    4656    IMPLICIT NONE
    4757
    48     INTEGER ::  i1, i2, j1, j2, k1, k2
     58    INTEGER(iwp) ::  i1  !:
     59    INTEGER(iwp) ::  i2  !:
     60    INTEGER(iwp) ::  j1  !:
     61    INTEGER(iwp) ::  j2  !:
     62    INTEGER(iwp) ::  k1  !:
     63    INTEGER(iwp) ::  k2  !:
    4964
    50     REAL, DIMENSION(i1:i2,j1:j2,k1:k2) ::  array
     65    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !:
    5166
    5267
     
    8196#if defined( __logging )
    8297
    83     USE control_parameters
     98    USE control_parameters,                                                    &
     99        ONLY:  log_message, simulated_time
     100
     101    USE kinds
     102           
    84103    USE pegrid
    85104
    86105    IMPLICIT NONE
    87106
    88     INTEGER ::  i1, i2, j1, j2
     107    INTEGER(iwp) ::  i1  !:
     108    INTEGER(iwp) ::  i2  !:
     109    INTEGER(iwp) ::  j1  !:
     110    INTEGER(iwp) ::  j2  !:
    89111
    90     REAL, DIMENSION(i1:i2,j1:j2) ::  array
     112    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !:
    91113
    92114
     
    121143#if defined( __logging )
    122144
    123     USE control_parameters
     145    USE control_parameters,                                                    &
     146        ONLY:  log_message, simulated_time
     147
     148    USE kinds
     149           
    124150    USE pegrid
    125151
    126152    IMPLICIT NONE
    127153
    128     INTEGER ::  i1, i2, j1, j2
     154    INTEGER(iwp) ::  i1  !:
     155    INTEGER(iwp) ::  i2  !:
     156    INTEGER(iwp) ::  j1  !:
     157    INTEGER(iwp) ::  j2  !:
    129158
    130     INTEGER, DIMENSION(i1:i2,j1:j2) ::  array
     159    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !:
    131160
    132161
Note: See TracChangeset for help on using the changeset viewer.