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

    r1310 r1320  
    2121! Current revisions:
    2222! ------------------
     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!
     
    3238! 1036 2012-10-22 13:43:42Z raasch
    3339! code put under GPL (PALM 3.9)
    34 !
    35 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    36 ! Array bounds and nx, ny adapted with nbgp
    37 !
    38 ! 622 2010-12-10 08:08:13Z raasch
    39 ! optional barriers included in order to speed up collective operations
    40 !
    41 ! Feb. 2007
    42 ! RCS Log replace by Id keyword, revision history cleaned up
    43 !
    44 ! Revision 1.4  2006/02/23 13:15:09  raasch
    45 ! nz_plot3d renamed nz_do3d
    4640!
    4741! Revision 1.1  1999/03/02 09:25:21  raasch
     
    6963!------------------------------------------------------------------------------!
    7064
     65    USE kinds
     66   
    7167    USE pegrid         !  needed for MPI_ALLREDUCE
    7268
    7369    IMPLICIT NONE
    7470
    75     INTEGER, PARAMETER   :: ip4 = SELECTED_INT_KIND ( 9 )
    76     INTEGER, PARAMETER   :: spk = SELECTED_REAL_KIND( 6 )
    77 
    78     INTEGER ::  ampl, dummy1, dummy2, factor, i, ifieldmax, ifieldmax_l, &
    79                 ifieldmin, ifieldmin_l, ii, length, nfree, npack, nsize, &
    80                 nx, ny, nz, startpos
    81     INTEGER(ip4) ::  imask (32)
    82     INTEGER(ip4), DIMENSION(:), ALLOCATABLE ::  ifield, packed_ifield
    83 
    84     INTEGER, INTENT(IN) ::  fid_avs, fid_fld, my_id, nxl, nxr, nyn, nys, nzb, &
    85                             nz_do3d, prec, nbgp
    86 
    87     REAL(spk), INTENT(IN) :: field(1:((nxr-nxl+1+2*nbgp)*(nyn-nys+1+2*nbgp)*(nz_do3d-nzb+1)))
     71    INTEGER(iwp) ::  ampl          !:
     72    INTEGER(iwp) ::  dummy1        !:
     73    INTEGER(iwp) ::  dummy2        !:
     74    INTEGER(iwp) ::  factor        !:
     75    INTEGER(iwp) ::  i             !:
     76    INTEGER(iwp) ::  ifieldmax     !:
     77    INTEGER(iwp) ::  ifieldmax_l   !:
     78    INTEGER(iwp) ::  ifieldmin     !:
     79    INTEGER(iwp) ::  ifieldmin_l   !:
     80    INTEGER(iwp) ::  ii            !:
     81    INTEGER(iwp) ::  length        !:
     82    INTEGER(iwp) ::  nfree         !:
     83    INTEGER(iwp) ::  npack         !:
     84    INTEGER(iwp) ::  nsize         !:
     85    INTEGER(iwp) ::  nx            !:
     86    INTEGER(iwp) ::  ny            !:
     87    INTEGER(iwp) ::  nz            !:
     88    INTEGER(iwp) ::  startpos      !:
     89   
     90    INTEGER(isp) ::  imask (32)    !:
     91   
     92    INTEGER(isp), DIMENSION(:), ALLOCATABLE ::  ifield          !:
     93    INTEGER(isp), DIMENSION(:), ALLOCATABLE ::  packed_ifield   !:
     94
     95    INTEGER, INTENT(IN) ::  fid_avs   !:
     96    INTEGER, INTENT(IN) ::  fid_fld   !:
     97    INTEGER, INTENT(IN) ::  my_id     !:
     98    INTEGER, INTENT(IN) ::  nxl       !:
     99    INTEGER, INTENT(IN) ::  nxr       !:
     100    INTEGER, INTENT(IN) ::  nyn       !:
     101    INTEGER, INTENT(IN) ::  nys       !:
     102    INTEGER, INTENT(IN) ::  nzb       !:
     103    INTEGER, INTENT(IN) ::  nz_do3d   !:
     104    INTEGER, INTENT(IN) ::  prec      !:
     105    INTEGER, INTENT(IN) ::  nbgp      !:
     106
     107    REAL(sp), INTENT(IN) ::  field(1:((nxr-nxl+1+2*nbgp)*(nyn-nys+1+2*nbgp)*(nz_do3d-nzb+1)))   !:
    88108
    89109!
     
    121141#if defined( __parallel )
    122142    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    123     CALL MPI_ALLREDUCE( ifieldmax_l, ifieldmax, 1, MPI_INTEGER, MPI_MAX, &
     143    CALL MPI_ALLREDUCE( ifieldmax_l, ifieldmax, 1, MPI_INTEGER, MPI_MAX,       &
    124144                        comm2d, ierr )
    125145    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    126     CALL MPI_ALLREDUCE( ifieldmin_l, ifieldmin, 1, MPI_INTEGER, MPI_MIN, &
     146    CALL MPI_ALLREDUCE( ifieldmin_l, ifieldmin, 1, MPI_INTEGER, MPI_MIN,       &
    127147                        comm2d, ierr )
    128148#else
     
    236256!
    237257!-- Formats
    238 100 FORMAT ('# precision = ',I4/ &
    239             '# feldmin   = ',I8/ &
    240             '# nbits     = ',I2/ &
     258100 FORMAT ('# precision = ',I4/                                               &
     259            '# feldmin   = ',I8/                                               &
     260            '# nbits     = ',I2/                                               &
    241261            '# nskip     = ',I8)
    242262
Note: See TracChangeset for help on using the changeset viewer.