Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (11 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_extend_tail_array.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! comment fields (!:) to be used for variable explanations added to
     26! all variable declaration statements
    2327!
    2428! Former revisions:
     
    3842!------------------------------------------------------------------------------!
    3943
    40     USE particle_attributes
     44    USE kinds
     45
     46    USE particle_attributes,                                                   &
     47        ONLY:  maximum_number_of_tails, maximum_number_of_tailpoints,          &
     48               new_tail_id, number_of_initial_tails, number_of_tails,          &
     49               particle_tail_coordinates, tail_mask, write_particle_statistics
    4150
    4251    IMPLICIT NONE
    4352
    44     INTEGER ::  new_maximum_number, number_of_new_tails
     53    INTEGER(iwp) ::  new_maximum_number                           !:
     54    INTEGER(iwp) ::  number_of_new_tails                          !:
    4555
    46     LOGICAL, DIMENSION(maximum_number_of_tails) ::  tmp_tail_mask
     56    LOGICAL, DIMENSION(maximum_number_of_tails) ::  tmp_tail_mask !:
    4757
    48     REAL, DIMENSION(maximum_number_of_tailpoints,5,maximum_number_of_tails) :: &
    49                                                     tmp_tail
     58    REAL(wp), DIMENSION(maximum_number_of_tailpoints,5,maximum_number_of_tails) :: &
     59                                                    tmp_tail      !:
    5060
    5161
Note: See TracChangeset for help on using the changeset viewer.