Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/exchange_horiz.f90

    r1678 r1682  
    1  SUBROUTINE exchange_horiz( ar, nbgp_local)
    2 
     1!> @file exchange_horiz.f90
    32!------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6968! Description:
    7069! ------------
    71 ! Exchange of lateral boundary values (parallel computers) and cyclic
    72 ! lateral boundary conditions, respectively.
    73 !------------------------------------------------------------------------------!
     70!> Exchange of lateral boundary values (parallel computers) and cyclic
     71!> lateral boundary conditions, respectively.
     72!------------------------------------------------------------------------------!
     73 SUBROUTINE exchange_horiz( ar, nbgp_local)
     74 
    7475
    7576    USE control_parameters,                                                    &
     
    9091
    9192
    92     INTEGER(iwp) ::  i           !:
    93     INTEGER(iwp) ::  j           !:
    94     INTEGER(iwp) ::  k           !:
    95     INTEGER(iwp) ::  nbgp_local  !:
     93    INTEGER(iwp) ::  i           !<
     94    INTEGER(iwp) ::  j           !<
     95    INTEGER(iwp) ::  k           !<
     96    INTEGER(iwp) ::  nbgp_local  !<
    9697   
    9798    REAL(wp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,               &
    98                         nxl-nbgp_local:nxr+nbgp_local) ::  ar  !:
     99                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !<
    99100                       
    100101
     
    290291
    291292
     293!------------------------------------------------------------------------------!
     294! Description:
     295! ------------
     296!> @todo Missing subroutine description.
     297!------------------------------------------------------------------------------!
    292298 SUBROUTINE exchange_horiz_int( ar, nbgp_local)
    293299
     
    305311
    306312
    307     INTEGER(iwp) ::  nbgp_local  !: number of ghost points
     313    INTEGER(iwp) ::  nbgp_local  !< number of ghost points
    308314   
    309315    INTEGER(iwp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,           &
    310                         nxl-nbgp_local:nxr+nbgp_local) ::  ar  !: treated array
     316                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !< treated array
    311317
    312318#if ! defined( __check )
Note: See TracChangeset for help on using the changeset viewer.