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

    r1665 r1682  
    1  SUBROUTINE message( routine_name, message_identifier, requested_action, &
    2                      message_level, output_on_pe, file_id, flush )
    3 
     1!> @file message.f90
    42!--------------------------------------------------------------------------------!
    53! This file is part of PALM.
     
    2119! Current revisions:
    2220! -----------------
    23 !
     21! Code annotations made doxygen readable
    2422!
    2523! Former revisions:
     
    5149! Description:
    5250! ------------
    53 ! Handling of the different kinds of messages.
    54 ! Meaning of formal parameters:
    55 ! requested_action: 0 - continue, 1 - abort by stop, 2 - abort by mpi_abort
    56 ! message_level: 0 - informative, 1 - warning, 2 - error
    57 ! output_on_pe: -1 - all, else - output on specified PE
    58 ! file_id: 6 - stdout (*)
    59 ! flush: 0 - no action, 1 - flush the respective output buffer
     51!> Handling of the different kinds of messages.
     52!> Meaning of formal parameters:
     53!> requested_action: 0 - continue, 1 - abort by stop, 2 - abort by mpi_abort
     54!> message_level: 0 - informative, 1 - warning, 2 - error
     55!> output_on_pe: -1 - all, else - output on specified PE
     56!> file_id: 6 - stdout (*)
     57!> flush: 0 - no action, 1 - flush the respective output buffer
    6058!------------------------------------------------------------------------------!
     59 SUBROUTINE message( routine_name, message_identifier, requested_action, &
     60                     message_level, output_on_pe, file_id, flush )
     61 
    6162
    6263    USE control_parameters,                                                    &
     
    6970    IMPLICIT NONE
    7071
    71     CHARACTER(LEN=6)   ::  message_identifier            !:
    72     CHARACTER(LEN=*)   ::  routine_name                  !:
    73     CHARACTER(LEN=200) ::  header_string                 !:
    74     CHARACTER(LEN=200) ::  information_string_1          !:
    75     CHARACTER(LEN=200) ::  information_string_2          !:
    76 
    77     INTEGER(iwp) ::  file_id                             !:
    78     INTEGER(iwp) ::  flush                               !:
    79     INTEGER(iwp) ::  i                                   !:
    80     INTEGER(iwp) ::  message_level                       !:
    81     INTEGER(iwp) ::  output_on_pe                        !:
    82     INTEGER(iwp) ::  requested_action                    !:
    83 
    84     LOGICAL ::  do_output                                !:
    85     LOGICAL ::  pe_out_of_range                          !:
     72    CHARACTER(LEN=6)   ::  message_identifier            !<
     73    CHARACTER(LEN=*)   ::  routine_name                  !<
     74    CHARACTER(LEN=200) ::  header_string                 !<
     75    CHARACTER(LEN=200) ::  information_string_1          !<
     76    CHARACTER(LEN=200) ::  information_string_2          !<
     77
     78    INTEGER(iwp) ::  file_id                             !<
     79    INTEGER(iwp) ::  flush                               !<
     80    INTEGER(iwp) ::  i                                   !<
     81    INTEGER(iwp) ::  message_level                       !<
     82    INTEGER(iwp) ::  output_on_pe                        !<
     83    INTEGER(iwp) ::  requested_action                    !<
     84
     85    LOGICAL ::  do_output                                !<
     86    LOGICAL ::  pe_out_of_range                          !<
    8687
    8788
     
    205206
    206207
    207  SUBROUTINE location_message( location, advance )
    208 
    209208!------------------------------------------------------------------------------!
    210209! Description:
    211210! ------------
    212 ! Prints out the given location on stdout
     211!> Prints out the given location on stdout
    213212!------------------------------------------------------------------------------!
     213 
     214 SUBROUTINE location_message( location, advance )
     215
    214216
    215217    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                        &
     
    221223    IMPLICIT NONE
    222224
    223     CHARACTER(LEN=*) ::  location !: text to be output on stdout
    224     LOGICAL          ::  advance  !: switch for advancing/noadvancing I/O
     225    CHARACTER(LEN=*) ::  location !< text to be output on stdout
     226    LOGICAL          ::  advance  !< switch for advancing/noadvancing I/O
    225227
    226228
Note: See TracChangeset for help on using the changeset viewer.