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

    r1319 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:
     
    2632! $Id$
    2733!
    28 ! 1318 2014-03-17 13:35:16Z raasch
    29 ! module interfaces removed
    30 !
    3134! 1092 2013-02-02 11:24:22Z raasch
    3235! unused variables removed
     
    3740! 841 2012-02-28 12:29:49Z maronga
    3841! Excluded routine from compilation of namelist_file_check
    39 !
    40 ! 707 2011-03-29 11:39:40Z raasch
    41 ! bc_lr/ns replaced by bc_lr/ns_cyc
    42 !
    43 ! 702 2011-03-24 19:33:15Z suehring
    44 ! Bugfix in declaration of ar in exchange_horiz_2d_int and number of MPI-blocks
    45 ! in MPI_SENDRECV().
    46 !
    47 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    48 ! Dynamic exchange of ghost points with nbgp, which depends on the advection
    49 ! scheme. Exchange between left and right PEs is now done with MPI-vectors.
    50 !
    51 ! 73 2007-03-20 08:33:14Z raasch
    52 ! Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary
    53 ! conditions
    54 !
    55 ! RCS Log replace by Id keyword, revision history cleaned up
    56 !
    57 ! Revision 1.9  2006/05/12 19:15:52  letzel
    58 ! MPI_REAL replaced by MPI_INTEGER in exchange_horiz_2d_int
    5942!
    6043! Revision 1.1  1998/01/23 09:58:21  raasch
     
    6851!------------------------------------------------------------------------------!
    6952
    70     USE control_parameters
    71     USE cpulog
    72     USE indices
     53    USE control_parameters,                                                    &
     54        ONLY :  inflow_l, inflow_n, inflow_r, inflow_s, outflow_l, outflow_n,  &
     55                outflow_r, outflow_s
     56               
     57    USE cpulog,                                                                &
     58        ONLY :  cpu_log, log_point_s
     59       
     60    USE indices,                                                               &
     61        ONLY :  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
     62       
     63    USE kinds
     64   
    7365    USE pegrid
    7466
     
    7668
    7769
    78     REAL ::  ar(nysg:nyng,nxlg:nxrg)
    79     INTEGER :: i
     70    INTEGER(iwp) :: i  !:
     71   
     72    REAL(wp) ::  ar(nysg:nyng,nxlg:nxrg)  !:
     73   
    8074
    8175#if ! defined( __check )
     
    188182!------------------------------------------------------------------------------!
    189183
    190     USE control_parameters
    191     USE cpulog
    192     USE indices
     184    USE control_parameters,                                                    &
     185        ONLY:  bc_lr_cyc, bc_ns_cyc
     186       
     187    USE cpulog,                                                                &
     188        ONLY:  cpu_log, log_point_s
     189       
     190    USE indices,                                                               &
     191        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
     192       
     193    USE kinds
     194   
    193195    USE pegrid
    194196
    195197    IMPLICIT NONE
    196198
    197     INTEGER ::  ar(nysg:nyng,nxlg:nxrg)
     199    INTEGER(iwp) ::  ar(nysg:nyng,nxlg:nxrg)  !:
    198200
    199201#if ! defined( __check )
Note: See TracChangeset for help on using the changeset viewer.