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/global_min_max.f90

    r1310 r1320  
    2121! Current revisions:
    2222! ------------------
    23 !
     23! ONLY-attribute added to USE-statements,
     24! kind-parameters added to all INTEGER and REAL declaration statements,
     25! kinds are defined in new module kinds,
     26! old module precision_kind is removed,
     27! revision history before 2012 removed,
     28! comment fields (!:) to be used for variable explanations added to
     29! all variable declaration statements
    2430!
    2531! Former revisions:
     
    3541! 866 2012-03-28 06:44:41Z raasch
    3642! new mode "absoff" accounts for an offset in the respective array
    37 !
    38 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    39 ! Adapting of the index arrays, because MINLOC assumes lowerbound at 1 and not
    40 ! at nbgp.
    41 !
    42 ! 622 2010-12-10 08:08:13Z raasch
    43 ! optional barriers included in order to speed up collective operations
    44 !
    45 ! Feb. 2007
    46 ! RCS Log replace by Id keyword, revision history cleaned up
    47 !
    48 ! Revision 1.11  2003/04/16 12:56:58  raasch
    49 ! Index values of the extrema are limited to the range 0..nx, 0..ny
    5043!
    5144! Revision 1.1  1997/07/24 11:14:03  raasch
     
    5851!------------------------------------------------------------------------------!
    5952
    60     USE indices
     53    USE indices,                                                               &
     54        ONLY:  nbgp, ny, nx
     55       
     56    USE kinds
     57   
    6158    USE pegrid
    6259
    6360    IMPLICIT NONE
    6461
    65     CHARACTER (LEN=*) ::  mode
    66 
    67     INTEGER           ::  i, i1, i2, id_fmax, id_fmin, j, j1, j2, k, k1, k2, &
    68                           fmax_ijk(3), fmax_ijk_l(3), fmin_ijk(3), &
    69                           fmin_ijk_l(3), value_ijk(3)
    70     INTEGER, OPTIONAL ::  value1_ijk(3)
    71     REAL              ::  offset, value, &
    72                           ar(i1:i2,j1:j2,k1:k2)
     62    CHARACTER (LEN=*) ::  mode  !:
     63
     64    INTEGER(iwp) ::  i              !:
     65    INTEGER(iwp) ::  i1             !:
     66    INTEGER(iwp) ::  i2             !:
     67    INTEGER(iwp) ::  id_fmax        !:
     68    INTEGER(iwp) ::  id_fmin        !:
     69    INTEGER(iwp) ::  j              !:
     70    INTEGER(iwp) ::  j1             !:
     71    INTEGER(iwp) ::  j2             !:
     72    INTEGER(iwp) ::  k              !:
     73    INTEGER(iwp) ::  k1             !:
     74    INTEGER(iwp) ::  k2             !:
     75    INTEGER(iwp) ::  fmax_ijk(3)    !:
     76    INTEGER(iwp) ::  fmax_ijk_l(3)  !:
     77    INTEGER(iwp) ::  fmin_ijk(3)    !:
     78    INTEGER(iwp) ::  fmin_ijk_l(3)  !:
     79    INTEGER(iwp) ::  value_ijk(3)   !:
     80   
     81    INTEGER(iwp), OPTIONAL ::  value1_ijk(3)  !:
     82   
     83    REAL(wp) ::  offset                 !:
     84    REAL(wp) ::  value                  !:
     85    REAL(wp) ::  ar(i1:i2,j1:j2,k1:k2)  !:
     86   
    7387#if defined( __ibm )
    74     REAL (KIND=4)     ::  fmax(2), fmax_l(2), fmin(2), fmin_l(2)  ! on 32bit-
    75                           ! machines MPI_2REAL must not be replaced by
    76                           ! MPI_2DOUBLE_PRECISION
    77 #else
    78     REAL              ::  fmax(2), fmax_l(2), fmin(2), fmin_l(2)
    79 #endif
    80     REAL, OPTIONAL    ::  value1
     88    REAL(sp) ::  fmax(2)    !:
     89    REAL(sp) ::  fmax_l(2)  !:
     90    REAL(sp) ::  fmin(2)    !:
     91    REAL(sp) ::  fmin_l(2)  !:
     92             ! on 32bit-machines MPI_2REAL must not be replaced
     93             ! by MPI_2DOUBLE_PRECISION
     94#else
     95    REAL(wp) ::  fmax(2)    !:
     96    REAL(wp) ::  fmax_l(2)  !:
     97    REAL(wp) ::  fmin(2)    !:
     98    REAL(wp) ::  fmin_l(2)  !:
     99#endif
     100    REAL(wp), OPTIONAL ::  value1  !:
    81101
    82102
Note: See TracChangeset for help on using the changeset viewer.