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

    r1321 r1682  
    1   SUBROUTINE init_coupling
    2 
     1!> @file init_coupling.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4241! Description:
    4342! ------------
    44 ! Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is
    45 ! called.
     43!> Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is
     44!> called.
    4645!------------------------------------------------------------------------------!
     46  SUBROUTINE init_coupling
     47 
    4748
    4849    USE control_parameters,                                                    &
     
    5758!
    5859!-- Local variables
    59     INTEGER(iwp) ::  i            !:
    60     INTEGER(iwp) ::  inter_color  !:
     60    INTEGER(iwp) ::  i            !<
     61    INTEGER(iwp) ::  inter_color  !<
    6162   
    62     INTEGER(iwp), DIMENSION(:) ::  bc_data(0:3) = 0  !:
     63    INTEGER(iwp), DIMENSION(:) ::  bc_data(0:3) = 0  !<
    6364
    6465!
Note: See TracChangeset for help on using the changeset viewer.