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/init_advec.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:
     
    3541! all actions concerning upstream-spline-method removed
    3642!
    37 ! RCS Log replace by Id keyword, revision history cleaned up
    38 !
    39 ! Revision 1.6  2004/04/30 11:59:31  raasch
    40 ! impulse_advec renamed momentum_advec
    41 !
    4243! Revision 1.1  1999/02/05 09:07:38  raasch
    4344! Initial revision
     
    4950!------------------------------------------------------------------------------!
    5051
    51     USE advection
    52     USE arrays_3d
    53     USE indices
    54     USE control_parameters
     52    USE advection,                                                             &
     53        ONLY:  aex, bex, dex, eex
     54       
     55    USE kinds
     56   
     57    USE control_parameters,                                                    &
     58        ONLY:  scalar_advec
    5559
    5660    IMPLICIT NONE
    5761
    58     INTEGER :: i, intervals, j
    59     REAL    :: delt, dn, dnneu, ex1, ex2, ex3, ex4, ex5, ex6, sterm
     62    INTEGER(iwp) ::  i          !:
     63    INTEGER(iwp) ::  intervals  !:
     64    INTEGER(iwp) ::  j          !:
     65   
     66    REAL(wp) :: delt   !:
     67    REAL(wp) :: dn     !:
     68    REAL(wp) :: dnneu  !:
     69    REAL(wp) :: ex1    !:
     70    REAL(wp) :: ex2    !:
     71    REAL(wp) :: ex3    !:
     72    REAL(wp) :: ex4    !:
     73    REAL(wp) :: ex5    !:
     74    REAL(wp) :: ex6    !:
     75    REAL(wp) :: sterm  !:
    6076
    6177
Note: See TracChangeset for help on using the changeset viewer.