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_s_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:
     
    3136! 1010 2012-09-20 07:59:54Z raasch
    3237! cpp switch __nopointer added for pointer free version
    33 !
    34 ! 19 2007-02-23 04:53:48Z raasch
    35 ! Calculation extended for gridpoint nzt
    36 !
    37 ! RCS Log replace by Id keyword, revision history cleaned up
    38 !
    39 ! Revision 1.12  2006/02/23 09:42:55  raasch
    40 ! nzb_2d replaced by nzb_s_inner
    4138!
    4239! Revision 1.1  1997/08/29 08:54:20  raasch
     
    7067    SUBROUTINE advec_s_pw( sk )
    7168
    72        USE arrays_3d
    73        USE control_parameters
    74        USE grid_variables
    75        USE indices
     69       USE arrays_3d,                                                          &
     70           ONLY:  dd2zu, tend, u, v, w
     71
     72       USE control_parameters,                                                 &
     73           ONLY:  u_gtrans, v_gtrans
     74
     75       USE grid_variables,                                                     &
     76           ONLY:  ddx, ddy
     77
     78       USE indices,                                                            &
     79           ONLY:  nxl, nxr, nyn, nys, nzb_s_inner, nzt
     80
     81       USE kinds
     82
    7683
    7784       IMPLICIT NONE
    7885
    79        INTEGER ::  i, j, k
     86       INTEGER(iwp) ::  i !:
     87       INTEGER(iwp) ::  j !:
     88       INTEGER(iwp) ::  k !:
    8089
    8190#if defined( __nopointer )
    82        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
     91       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
    8392#else
    84        REAL, DIMENSION(:,:,:), POINTER ::  sk
     93       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    8594#endif
    8695 
     
    111120    SUBROUTINE advec_s_pw_ij( i, j, sk )
    112121
    113        USE arrays_3d
    114        USE control_parameters
    115        USE grid_variables
    116        USE indices
     122       USE arrays_3d,                                                          &
     123           ONLY:  dd2zu, tend, u, v, w
     124
     125       USE control_parameters,                                                 &
     126           ONLY:  u_gtrans, v_gtrans
     127
     128       USE grid_variables,                                                     &
     129           ONLY:  ddx, ddy
     130
     131       USE indices,                                                            &
     132           ONLY:  nzb_s_inner, nzt
     133
     134       USE kinds
     135
    117136
    118137       IMPLICIT NONE
    119138
    120        INTEGER ::  i, j, k
     139       INTEGER(iwp) ::  i !:
     140       INTEGER(iwp) ::  j !:
     141       INTEGER(iwp) ::  k !:
    121142
    122143#if defined( __nopointer )
    123        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
     144       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
    124145#else
    125        REAL, DIMENSION(:,:,:), POINTER ::  sk
     146       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    126147#endif
    127148
Note: See TracChangeset for help on using the changeset viewer.