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_pegrid.f90

    r1678 r1682  
    1  SUBROUTINE init_pegrid
    2 
     1!> @file init_pegrid.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    114113! Description:
    115114! ------------
    116 ! Determination of the virtual processor topology (if not prescribed by the
    117 ! user)and computation of the grid point number and array bounds of the local
    118 ! domains.
     115!> Determination of the virtual processor topology (if not prescribed by the
     116!> user)and computation of the grid point number and array bounds of the local
     117!> domains.
    119118!------------------------------------------------------------------------------!
     119 SUBROUTINE init_pegrid
     120 
    120121
    121122    USE control_parameters,                                                    &
     
    149150    IMPLICIT NONE
    150151
    151     INTEGER(iwp) ::  i                        !:
    152     INTEGER(iwp) ::  id_inflow_l              !:
    153     INTEGER(iwp) ::  id_recycling_l           !:
    154     INTEGER(iwp) ::  ind(5)                   !:
    155     INTEGER(iwp) ::  j                        !:
    156     INTEGER(iwp) ::  k                        !:
    157     INTEGER(iwp) ::  maximum_grid_level_l     !:
    158     INTEGER(iwp) ::  mg_levels_x              !:
    159     INTEGER(iwp) ::  mg_levels_y              !:
    160     INTEGER(iwp) ::  mg_levels_z              !:
    161     INTEGER(iwp) ::  mg_switch_to_pe0_level_l !:
    162     INTEGER(iwp) ::  nnx_y                    !:
    163     INTEGER(iwp) ::  nnx_z                    !:
    164     INTEGER(iwp) ::  nny_x                    !:
    165     INTEGER(iwp) ::  nny_z                    !:
    166     INTEGER(iwp) ::  nnz_x                    !:
    167     INTEGER(iwp) ::  nnz_y                    !:
    168     INTEGER(iwp) ::  numproc_sqr              !:
    169     INTEGER(iwp) ::  nxl_l                    !:
    170     INTEGER(iwp) ::  nxr_l                    !:
    171     INTEGER(iwp) ::  nyn_l                    !:
    172     INTEGER(iwp) ::  nys_l                    !:
    173     INTEGER(iwp) ::  nzb_l                    !:
    174     INTEGER(iwp) ::  nzt_l                    !:
    175     INTEGER(iwp) ::  omp_get_num_threads      !:
    176 
    177     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ind_all !:
    178     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxlf    !:
    179     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxrf    !:
    180     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nynf    !:
    181     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nysf    !:
    182 
    183     INTEGER(iwp), DIMENSION(2) :: pdims_remote          !:
     152    INTEGER(iwp) ::  i                        !<
     153    INTEGER(iwp) ::  id_inflow_l              !<
     154    INTEGER(iwp) ::  id_recycling_l           !<
     155    INTEGER(iwp) ::  ind(5)                   !<
     156    INTEGER(iwp) ::  j                        !<
     157    INTEGER(iwp) ::  k                        !<
     158    INTEGER(iwp) ::  maximum_grid_level_l     !<
     159    INTEGER(iwp) ::  mg_levels_x              !<
     160    INTEGER(iwp) ::  mg_levels_y              !<
     161    INTEGER(iwp) ::  mg_levels_z              !<
     162    INTEGER(iwp) ::  mg_switch_to_pe0_level_l !<
     163    INTEGER(iwp) ::  nnx_y                    !<
     164    INTEGER(iwp) ::  nnx_z                    !<
     165    INTEGER(iwp) ::  nny_x                    !<
     166    INTEGER(iwp) ::  nny_z                    !<
     167    INTEGER(iwp) ::  nnz_x                    !<
     168    INTEGER(iwp) ::  nnz_y                    !<
     169    INTEGER(iwp) ::  numproc_sqr              !<
     170    INTEGER(iwp) ::  nxl_l                    !<
     171    INTEGER(iwp) ::  nxr_l                    !<
     172    INTEGER(iwp) ::  nyn_l                    !<
     173    INTEGER(iwp) ::  nys_l                    !<
     174    INTEGER(iwp) ::  nzb_l                    !<
     175    INTEGER(iwp) ::  nzt_l                    !<
     176    INTEGER(iwp) ::  omp_get_num_threads      !<
     177
     178    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ind_all !<
     179    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxlf    !<
     180    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxrf    !<
     181    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nynf    !<
     182    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nysf    !<
     183
     184    INTEGER(iwp), DIMENSION(2) :: pdims_remote          !<
    184185
    185186#if defined( __mpi2 )
    186     LOGICAL ::  found                                   !:
     187    LOGICAL ::  found                                   !<
    187188#endif
    188189
Note: See TracChangeset for help on using the changeset viewer.