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/advec_u_pw.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! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    2833! 1036 2012-10-22 13:43:42Z raasch
    2934! code put under GPL (PALM 3.9)
    30 !
    31 ! 106 2007-08-16 14:30:26Z raasch
    32 ! i loop is starting from nxlu (needed for non-cyclic boundary conditions)
    33 !
    34 ! 75 2007-03-22 09:54:05Z raasch
    35 ! uxrp eliminated
    36 !
    37 ! RCS Log replace by Id keyword, revision history cleaned up
    38 !
    39 ! Revision 1.15  2006/02/23 09:44:21  raasch
    40 ! nzb_2d replaced by nzb_u_inner
    4135!
    4236! Revision 1.1  1997/08/11 06:09:21  raasch
     
    6862    SUBROUTINE advec_u_pw
    6963
    70        USE arrays_3d
    71        USE control_parameters
    72        USE grid_variables
    73        USE indices
     64       USE arrays_3d,                                                          &
     65           ONLY:  ddzw, tend, u, v, w
     66
     67       USE control_parameters,                                                 &
     68           ONLY:  u_gtrans, v_gtrans
     69
     70       USE grid_variables,                                                     &
     71           ONLY:  ddx, ddy
     72
     73       USE indices,                                                            &
     74           ONLY:  nxlu, nxr, nyn, nys, nzb_u_inner, nzt
     75
     76       USE kinds
     77
    7478
    7579       IMPLICIT NONE
    7680
    77        INTEGER ::  i, j, k
    78        REAL    ::  gu, gv
     81       INTEGER(iwp) ::  i !:
     82       INTEGER(iwp) ::  j !:
     83       INTEGER(iwp) ::  k !:
     84       
     85       REAL(wp)    ::  gu !:
     86       REAL(wp)    ::  gv !:
    7987 
    8088       gu = 2.0 * u_gtrans
     
    104112    SUBROUTINE advec_u_pw_ij( i, j )
    105113
    106        USE arrays_3d
    107        USE control_parameters
    108        USE grid_variables
    109        USE indices
     114       USE arrays_3d,                                                          &
     115           ONLY:  ddzw, tend, u, v, w
     116
     117       USE control_parameters,                                                 &
     118           ONLY:  u_gtrans, v_gtrans
     119
     120       USE grid_variables,                                                     &
     121           ONLY:  ddx, ddy
     122
     123       USE indices,                                                            &
     124           ONLY:  nzb_u_inner, nzt
     125
     126       USE kinds
     127
    110128
    111129       IMPLICIT NONE
    112130
    113        INTEGER ::  i, j, k
    114        REAL    ::  gu, gv
     131       INTEGER(iwp) ::  i !:
     132       INTEGER(iwp) ::  j !:
     133       INTEGER(iwp) ::  k !:
     134       
     135       REAL(wp)    ::  gu !:
     136       REAL(wp)    ::  gv !:
    115137
    116138       gu = 2.0 * u_gtrans
Note: See TracChangeset for help on using the changeset viewer.