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/surface_coupler.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:
     
    3743! 880 2012-04-13 06:28:59Z raasch
    3844! Bugfix: preprocessor statements for parallel execution added
    39 !
    40 ! 709 2011-03-30 09:31:40Z raasch
    41 ! formatting adjustments
    42 !
    43 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    44 ! Additional case for nonequivalent processor and grid topopolgy in ocean and
    45 ! atmosphere added (coupling_topology = 1).
    46 ! Added exchange of u and v from Ocean to Atmosphere
    47 !
    48 ! 291 2009-04-16 12:07:26Z raasch
    49 ! Coupling with independent precursor runs.
    50 ! Output of messages replaced by message handling routine.
    51 !
    52 ! 206 2008-10-13 14:59:11Z raasch
    53 ! Implementation of a MPI-1 Coupling: replaced myid with target_id,
    54 ! deleted __mpi2 directives
    5545!
    5646! 109 2007-08-28 15:26:47Z letzel
     
    6252!------------------------------------------------------------------------------!
    6353
    64     USE arrays_3d
    65     USE control_parameters
    66     USE cpulog
    67     USE grid_variables
    68     USE indices
     54    USE arrays_3d,                                                             &
     55        ONLY:  pt, shf, qsws, qswst_remote, rho, sa, saswst, total_2d_a,       &
     56               total_2d_o, tswst, u, usws, uswst, v, vsws, vswst
     57
     58    USE control_parameters,                                                    &
     59        ONLY:  coupling_mode, coupling_mode_remote, coupling_topology,         &
     60               humidity, humidity_remote, message_string, terminate_coupled,   &
     61               terminate_coupled_remote, time_since_reference_point
     62
     63    USE cpulog,                                                                &
     64        ONLY:  cpu_log, log_point
     65
     66    USE indices,                                                               &
     67        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_a, nx_o, ny, nyn, nyng, nys, &
     68               nysg, ny_a, ny_o, nzt
     69
     70    USE kinds
     71
    6972    USE pegrid
    7073
    7174    IMPLICIT NONE
    7275
    73     REAL    ::  time_since_reference_point_rem
    74     REAL    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp)
     76    REAL(wp)    ::  time_since_reference_point_rem        !:
     77    REAL(wp)    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp) !:
    7578
    7679#if defined( __parallel )
     
    418421#if defined( __parallel )
    419422
    420     USE arrays_3d
    421     USE control_parameters
    422     USE grid_variables
    423     USE indices
    424     USE pegrid
     423    USE arrays_3d,                                                             &
     424        ONLY:  total_2d_a, total_2d_o
     425
     426    USE indices,                                                               &
     427        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
     428
     429    USE kinds
     430
     431    USE pegrid,                                                                &
     432        ONLY:  comm2d, comm_inter, ierr, MPI_DOUBLE_PRECISION, myid, ngp_a,    &
     433               target_id
    425434
    426435    IMPLICIT NONE
    427436
    428     INTEGER             ::  dnx, dnx2, dny, dny2, i, ii, j, jj
    429     INTEGER, intent(in) ::  tag
     437    INTEGER(iwp) ::  dnx  !:
     438    INTEGER(iwp) ::  dnx2 !:
     439    INTEGER(iwp) ::  dny  !:
     440    INTEGER(iwp) ::  dny2 !:
     441    INTEGER(iwp) ::  i    !:
     442    INTEGER(iwp) ::  ii   !:
     443    INTEGER(iwp) ::  j    !:
     444    INTEGER(iwp) ::  jj   !:
     445
     446    INTEGER(iwp), intent(in) ::  tag !:
    430447
    431448    CALL MPI_BARRIER( comm2d, ierr )
     
    490507#if defined( __parallel )
    491508
    492     USE arrays_3d
    493     USE control_parameters
    494     USE grid_variables
    495     USE indices
    496     USE pegrid
     509    USE arrays_3d,                                                             &
     510        ONLY:  total_2d_a, total_2d_o
     511
     512    USE indices,                                                               &
     513        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
     514
     515    USE kinds
     516
     517    USE pegrid,                                                                &
     518        ONLY:  comm2d, comm_inter, ierr, MPI_DOUBLE_PRECISION, myid, ngp_o,    &
     519               target_id
    497520
    498521    IMPLICIT NONE
    499522
    500     INTEGER             ::  dnx, dny, i, ii, j, jj
    501     INTEGER, intent(in) ::  tag
    502     REAL                ::  fl, fr, myl, myr
    503 
     523    INTEGER(iwp)             ::  dnx !:
     524    INTEGER(iwp)             ::  dny !:
     525    INTEGER(iwp)             ::  i   !:
     526    INTEGER(iwp)             ::  ii  !:
     527    INTEGER(iwp)             ::  j   !:
     528    INTEGER(iwp)             ::  jj  !:
     529    INTEGER(iwp), intent(in) ::  tag !:
     530
     531    REAL(wp)                 ::  fl  !:
     532    REAL(wp)                 ::  fr  !:
     533    REAL(wp)                 ::  myl !:
     534    REAL(wp)                 ::  myr !:
    504535
    505536    CALL MPI_BARRIER( comm2d, ierr )
Note: See TracChangeset for help on using the changeset viewer.