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/tridia_solver.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:
     
    5561!------------------------------------------------------------------------------!
    5662
    57     USE indices
    58     USE transpose_indices
     63    USE indices,                                                               &
     64        ONLY:  nx, ny, nz
     65
     66    USE kinds
     67
     68    USE transpose_indices,                                                     &
     69        ONLY:  nxl_z, nyn_z, nxr_z, nys_z
    5970
    6071    IMPLICIT NONE
    6172
    62     REAL, DIMENSION(:,:), ALLOCATABLE ::  ddzuw
     73    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddzuw !:
    6374
    6475    PRIVATE
     
    7990    SUBROUTINE tridia_init
    8091
    81        USE arrays_3d,  ONLY:  ddzu_pres, ddzw
     92       USE arrays_3d,                                                          &
     93           ONLY:  ddzu_pres, ddzw
     94
     95       USE kinds
    8296
    8397       IMPLICIT NONE
    8498
    85        INTEGER ::  k
     99       INTEGER(iwp) ::  k !:
    86100
    87101       ALLOCATE( ddzuw(0:nz-1,3) )
     
    109123!------------------------------------------------------------------------------!
    110124
    111           USE arrays_3d,  ONLY: tric
    112           USE constants
    113           USE control_parameters
    114           USE grid_variables
     125          USE arrays_3d,                                                       &
     126              ONLY:  tric
     127
     128          USE constants,                                                       &
     129              ONLY:  pi
     130
     131          USE control_parameters,                                              &
     132              ONLY:  ibc_p_b, ibc_p_t
     133
     134          USE grid_variables,                                                  &
     135              ONLY:  dx, dy
     136
     137
     138          USE kinds
    115139
    116140          IMPLICIT NONE
    117141
    118           INTEGER ::  i, j, k, nnxh, nnyh
    119 
    120           REAL    ::  ll(nxl_z:nxr_z,nys_z:nyn_z)
     142          INTEGER(iwp) ::  i    !:
     143          INTEGER(iwp) ::  j    !:
     144          INTEGER(iwp) ::  k    !:
     145          INTEGER(iwp) ::  nnxh !:
     146          INTEGER(iwp) ::  nnyh !:
     147
     148          REAL(wp)    ::  ll(nxl_z:nxr_z,nys_z:nyn_z) !:
    121149          !$acc declare create( ll )
    122150
     
    201229!------------------------------------------------------------------------------!
    202230
    203           USE arrays_3d,  ONLY: tri
    204           USE control_parameters
     231          USE arrays_3d,                                                       &
     232              ONLY:  tri
     233
     234          USE control_parameters,                                              &
     235              ONLY:  ibc_p_b, ibc_p_t
     236
     237          USE kinds
    205238
    206239          IMPLICIT NONE
    207240
    208           INTEGER ::  i, j, k
    209 
    210           REAL    ::  ar(nxl_z:nxr_z,nys_z:nyn_z,1:nz)
    211 
    212           REAL, DIMENSION(nxl_z:nxr_z,nys_z:nyn_z,0:nz-1)   ::  ar1
     241          INTEGER(iwp) ::  i !:
     242          INTEGER(iwp) ::  j !:
     243          INTEGER(iwp) ::  k !:
     244
     245          REAL(wp)     ::  ar(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !:
     246
     247          REAL(wp), DIMENSION(nxl_z:nxr_z,nys_z:nyn_z,0:nz-1)   ::  ar1 !:
    213248          !$acc declare create( ar1 )
    214249
     
    275310!------------------------------------------------------------------------------!
    276311
    277           USE arrays_3d,  ONLY: tri
    278           USE control_parameters
     312          USE arrays_3d,                                                       &
     313              ONLY:  tri
     314
     315          USE control_parameters,                                              &
     316              ONLY:  ibc_p_b, ibc_p_t
     317
     318          USE kinds
    279319
    280320          IMPLICIT NONE
    281321
    282           INTEGER ::  i, j, jj, k
    283 
    284           REAL    ::  ar(nxl_z:nxr_z,nys_z:nyn_z,1:nz)
     322          INTEGER(iwp) ::  i  !:
     323          INTEGER(iwp) ::  j  !:
     324          INTEGER(iwp) ::  jj !:
     325          INTEGER(iwp) ::  k  !:
     326
     327          REAL(wp)     ::  ar(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !:
    285328
    286329          !$acc declare create( ar1 )
    287           REAL, DIMENSION(nxl_z:nxr_z,nys_z:nyn_z,0:nz-1)   ::  ar1
     330          REAL(wp), DIMENSION(nxl_z:nxr_z,nys_z:nyn_z,0:nz-1) ::  ar1 !:
    288331
    289332!
     
    350393!------------------------------------------------------------------------------!
    351394
    352           USE arrays_3d,  ONLY: tri, tric
     395          USE arrays_3d,                                                       &
     396              ONLY:  tri, tric
     397
     398          USE kinds
    353399
    354400          IMPLICIT NONE
    355401
    356           INTEGER ::  i, j, k
    357 
     402          INTEGER(iwp) ::  i !:
     403          INTEGER(iwp) ::  j !:
     404          INTEGER(iwp) ::  k !:
    358405!
    359406!--       Splitting
     
    398445!------------------------------------------------------------------------------!
    399446
    400        USE arrays_3d
    401        USE control_parameters
    402 
    403        USE pegrid
     447       USE arrays_3d,                                                          &
     448           ONLY:  ddzu_pres, ddzw
     449
     450       USE control_parameters,                                                 &
     451           ONLY:  ibc_p_b, ibc_p_t
     452
     453       USE kinds
    404454
    405455       IMPLICIT NONE
    406456
    407        INTEGER ::  i, j, k, nnyh, nx, ny, omp_get_thread_num, tn
    408 
    409        REAL    ::  ddx2, ddy2
    410 
    411        REAL, DIMENSION(0:nx,1:nz)     ::  ar
    412        REAL, DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d
     457       INTEGER(iwp) ::  i                  !:
     458       INTEGER(iwp) ::  j                  !:
     459       INTEGER(iwp) ::  k                  !:
     460       INTEGER(iwp) ::  nnyh               !:
     461       INTEGER(iwp) ::  nx                 !:
     462       INTEGER(iwp) ::  ny                 !:
     463       INTEGER(iwp) ::  omp_get_thread_num !:
     464       INTEGER(iwp) ::  tn                 !:
     465
     466       REAL(wp)     ::  ddx2 !:
     467       REAL(wp)     ::  ddy2 !:
     468
     469       REAL(wp), DIMENSION(0:nx,1:nz)     ::  ar         !:
     470       REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !:
    413471
    414472
     
    465523!------------------------------------------------------------------------------!
    466524
    467           USE constants
     525          USE constants,                                                       &
     526              ONLY:  pi
     527
     528          USE kinds
    468529
    469530          IMPLICIT NONE
    470531
    471           INTEGER ::  i, j, k, nnxh
    472           REAL    ::  a, c
    473 
    474           REAL, DIMENSION(0:nx) ::  l
     532          INTEGER(iwp) ::  i    !:
     533          INTEGER(iwp) ::  j    !:
     534          INTEGER(iwp) ::  k    !:
     535          INTEGER(iwp) ::  nnxh !:
     536
     537          REAL(wp)     ::  a !:
     538          REAL(wp)     ::  c !:
     539
     540          REAL(wp), DIMENSION(0:nx) ::  l !:
    475541
    476542#if defined( __intel11 )
    477           REAL, DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d
     543          REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !:
    478544#endif
    479545
     
    533599          IMPLICIT NONE
    534600
    535           INTEGER ::  i, k
     601          INTEGER(iwp) ::  i !:
     602          INTEGER(iwp) ::  k !:
    536603
    537604#if defined( __intel11 )
    538           REAL, DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d
     605          REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !:
    539606#endif
    540607
     
    563630          IMPLICIT NONE
    564631
    565           INTEGER ::  i, k
    566 
    567           REAL, DIMENSION(0:nx,nz)       ::  ar
    568           REAL, DIMENSION(0:nx,0:nz-1)   ::  ar1
    569           REAL, DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d
     632          INTEGER(iwp) ::  i !:
     633          INTEGER(iwp) ::  k !:
     634
     635          REAL(wp), DIMENSION(0:nx,nz)       ::  ar         !:
     636          REAL(wp), DIMENSION(0:nx,0:nz-1)   ::  ar1        !:
     637          REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !:
    570638
    571639!
Note: See TracChangeset for help on using the changeset viewer.