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

    r1354 r1682  
    1   SUBROUTINE init_dvrp
    2 
     1!> @file init_dvrp.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4948! Description:
    5049! ------------
    51 ! Initializing actions needed when using dvrp-software
     50!> Initializing actions needed when using dvrp-software
    5251!------------------------------------------------------------------------------!
     52  SUBROUTINE init_dvrp
     53 
    5354#if defined( __dvrp_graphics )
    5455
     
    7576    IMPLICIT NONE
    7677
    77     CHARACTER (LEN=2)  ::  section_chr      !:
    78     CHARACTER (LEN=3)  ::  prefix_chr       !:
    79     CHARACTER (LEN=80) ::  dvrp_file_local  !:
    80    
    81     INTEGER(iwp) ::  cluster_mode      !:
    82     INTEGER(iwp) ::  cluster_size_x    !:
    83     INTEGER(iwp) ::  cluster_size_y    !:
    84     INTEGER(iwp) ::  cluster_size_z    !:
    85     INTEGER(iwp) ::  gradient_normals  !:
    86     INTEGER(iwp) ::  i                 !:
    87     INTEGER(iwp) ::  j                 !:
    88     INTEGER(iwp) ::  k                 !:
    89     INTEGER(iwp) ::  l                 !:
    90     INTEGER(iwp) ::  m                 !:
    91     INTEGER(iwp) ::  nx_dvrp_l         !:
    92     INTEGER(iwp) ::  nx_dvrp_r         !:
    93     INTEGER(iwp) ::  ny_dvrp_n         !:
    94     INTEGER(iwp) ::  ny_dvrp_s         !:
    95     INTEGER(iwp) ::  pn                !:
    96     INTEGER(iwp) ::  tv                !:
    97     INTEGER(iwp) ::  vn                !:
     78    CHARACTER (LEN=2)  ::  section_chr      !<
     79    CHARACTER (LEN=3)  ::  prefix_chr       !<
     80    CHARACTER (LEN=80) ::  dvrp_file_local  !<
     81   
     82    INTEGER(iwp) ::  cluster_mode      !<
     83    INTEGER(iwp) ::  cluster_size_x    !<
     84    INTEGER(iwp) ::  cluster_size_y    !<
     85    INTEGER(iwp) ::  cluster_size_z    !<
     86    INTEGER(iwp) ::  gradient_normals  !<
     87    INTEGER(iwp) ::  i                 !<
     88    INTEGER(iwp) ::  j                 !<
     89    INTEGER(iwp) ::  k                 !<
     90    INTEGER(iwp) ::  l                 !<
     91    INTEGER(iwp) ::  m                 !<
     92    INTEGER(iwp) ::  nx_dvrp_l         !<
     93    INTEGER(iwp) ::  nx_dvrp_r         !<
     94    INTEGER(iwp) ::  ny_dvrp_n         !<
     95    INTEGER(iwp) ::  ny_dvrp_s         !<
     96    INTEGER(iwp) ::  pn                !<
     97    INTEGER(iwp) ::  tv                !<
     98    INTEGER(iwp) ::  vn                !<
    9899                     
    99     LOGICAL  ::  allocated  !:
    100    
    101     REAL(sp) ::  center(3)      !:
    102     REAL(sp) ::  cluster_alpha  !:
    103     REAL(sp) ::  distance       !:
    104     REAL(sp) ::  tmp_b          !:
    105     REAL(sp) ::  tmp_g          !:
    106     REAL(sp) ::  tmp_r          !:
    107     REAL(sp) ::  tmp_t          !:
    108     REAL(sp) ::  tmp_th         !:
    109     REAL(sp) ::  tmp_thr        !:
    110     REAL(sp) ::  tmp_x1         !:
    111     REAL(sp) ::  tmp_x2         !:
    112     REAL(sp) ::  tmp_y1         !:
    113     REAL(sp) ::  tmp_y2         !:
    114     REAL(sp) ::  tmp_z1         !:
    115     REAL(sp) ::  tmp_z2         !:
    116     REAL(sp) ::  tmp_1          !:
    117     REAL(sp) ::  tmp_2          !:
    118     REAL(sp) ::  tmp_3          !:
    119     REAL(sp) ::  tmp_4          !:
    120     REAL(sp) ::  tmp_5          !:
    121     REAL(sp) ::  tmp_6          !:
    122     REAL(sp) ::  tmp_7          !:
    123 
    124     REAL(sp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf  !:
    125 
    126     TYPE(CSTRING), SAVE ::  dvrp_directory_c   !:
    127     TYPE(CSTRING), SAVE ::  dvrp_file_c        !:
    128     TYPE(CSTRING), SAVE ::  dvrp_file_local_c  !:
    129     TYPE(CSTRING), SAVE ::  dvrp_host_c        !:
    130     TYPE(CSTRING), SAVE ::  dvrp_password_c    !:
    131     TYPE(CSTRING), SAVE ::  dvrp_username_c    !:
    132     TYPE(CSTRING), SAVE ::  name_c             !:
     100    LOGICAL  ::  allocated  !<
     101   
     102    REAL(sp) ::  center(3)      !<
     103    REAL(sp) ::  cluster_alpha  !<
     104    REAL(sp) ::  distance       !<
     105    REAL(sp) ::  tmp_b          !<
     106    REAL(sp) ::  tmp_g          !<
     107    REAL(sp) ::  tmp_r          !<
     108    REAL(sp) ::  tmp_t          !<
     109    REAL(sp) ::  tmp_th         !<
     110    REAL(sp) ::  tmp_thr        !<
     111    REAL(sp) ::  tmp_x1         !<
     112    REAL(sp) ::  tmp_x2         !<
     113    REAL(sp) ::  tmp_y1         !<
     114    REAL(sp) ::  tmp_y2         !<
     115    REAL(sp) ::  tmp_z1         !<
     116    REAL(sp) ::  tmp_z2         !<
     117    REAL(sp) ::  tmp_1          !<
     118    REAL(sp) ::  tmp_2          !<
     119    REAL(sp) ::  tmp_3          !<
     120    REAL(sp) ::  tmp_4          !<
     121    REAL(sp) ::  tmp_5          !<
     122    REAL(sp) ::  tmp_6          !<
     123    REAL(sp) ::  tmp_7          !<
     124
     125    REAL(sp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf  !<
     126
     127    TYPE(CSTRING), SAVE ::  dvrp_directory_c   !<
     128    TYPE(CSTRING), SAVE ::  dvrp_file_c        !<
     129    TYPE(CSTRING), SAVE ::  dvrp_file_local_c  !<
     130    TYPE(CSTRING), SAVE ::  dvrp_host_c        !<
     131    TYPE(CSTRING), SAVE ::  dvrp_password_c    !<
     132    TYPE(CSTRING), SAVE ::  dvrp_username_c    !<
     133    TYPE(CSTRING), SAVE ::  name_c             !<
    133134
    134135!
     
    741742
    742743 
    743  SUBROUTINE init_dvrp_logging
    744 
    745744!------------------------------------------------------------------------------!
    746745! Description:
    747746! ------------
    748 ! Initializes logging events for time measurement with dvrp software
    749 ! and splits one PE from the global communicator in case that dvrp output
    750 ! shall be done by one single PE.
     747!> Initializes logging events for time measurement with dvrp software
     748!> and splits one PE from the global communicator in case that dvrp output
     749!> shall be done by one single PE.
    751750!------------------------------------------------------------------------------!
     751 
     752 SUBROUTINE init_dvrp_logging
     753
    752754#if defined( __dvrp_graphics )
    753755
     
    761763    IMPLICIT NONE
    762764
    763     CHARACTER (LEN=4) ::  chr  !:
    764    
    765     INTEGER(iwp) ::  idummy    !:
     765    CHARACTER (LEN=4) ::  chr  !<
     766   
     767    INTEGER(iwp) ::  idummy    !<
    766768
    767769!
     
    808810
    809811
    810  SUBROUTINE close_dvrp
    811 
    812812!------------------------------------------------------------------------------!
    813813! Description:
    814814! ------------
    815 ! Exit of dvrp software and finish dvrp logging
     815!> Exit of dvrp software and finish dvrp logging
    816816!------------------------------------------------------------------------------!
     817 
     818 SUBROUTINE close_dvrp
     819
    817820#if defined( __dvrp_graphics )
    818821                                               
     
    824827    USE kinds
    825828
    826     INTEGER(iwp) ::  m  !:
     829    INTEGER(iwp) ::  m  !<
    827830
    828831!
Note: See TracChangeset for help on using the changeset viewer.