Ignore:
Timestamp:
Sep 14, 2020 7:55:28 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4580 r4677  
    11!> @file message.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4580 2020-06-29 07:54:21Z raasch
    2729! bugfix for aborts in case of nested runs
    28 ! 
     30!
    2931! 4578 2020-06-25 15:43:32Z gronemeier
    3032! bugfix : do not save input values from last call of routines debug_message and location_message
     
    4547!
    4648! 3885 2019-04-11 11:29:34Z kanani
    47 ! Changes related to global restructuring of location messages and introduction
    48 ! of additional debug messages
     49! Changes related to global restructuring of location messages and introduction of additional debug
     50! messages
    4951!
    5052! 3655 2019-01-07 16:51:22Z knoop
     
    6466!> file_id: 6 - stdout (*)
    6567!> flush_file: 0 - no action, 1 - flush the respective output buffer
    66 !------------------------------------------------------------------------------!
    67  SUBROUTINE message( routine_name, message_identifier, requested_action, &
    68                      message_level, output_on_pe, file_id, flush_file )
    69 
    70     USE control_parameters,                                                    &
     68!--------------------------------------------------------------------------------------------------!
     69 SUBROUTINE message( routine_name, message_identifier, requested_action, message_level,            &
     70                     output_on_pe, file_id, flush_file )
     71
     72    USE control_parameters,                                                                        &
    7173        ONLY:  abort_mode, message_string
    7274
     
    7577    USE pegrid
    7678
    77     USE pmc_interface,                                                         &
     79    USE pmc_interface,                                                                             &
    7880        ONLY:  cpl_id, nested_run
    7981
     
    112114!-- Create the complete output string, starting with the message level
    113115    IF ( message_level == 0 )  THEN
    114        header_string = '--- informative message' // TRIM(nest_string) //       &
    115                        ' ---'
     116       header_string = '--- informative message' // TRIM(nest_string) // ' ---'
    116117    ELSEIF ( message_level == 1 )  THEN
    117118       header_string = '+++ warning message' // TRIM(nest_string) // ' ---'
     
    119120       header_string = '+++ error message' // TRIM(nest_string) // ' ---'
    120121    ELSE
    121        WRITE( header_string,'(A,I2)' )  '+++ unknown message level' //         &
    122                                         TRIM(nest_string) // ': ',             &
    123                                         message_level
     122       WRITE( header_string,'(A,I2)' )  '+++ unknown message level' //                             &
     123                                        TRIM(nest_string) // ': ', message_level
    124124    ENDIF
    125125
    126126!
    127127!-- Add the message identifier and the generating routine
    128     header_string_2 = 'ID: ' // message_identifier // &
     128    header_string_2 = 'ID: ' // message_identifier //                                              &
    129129                      '  generated by routine: ' // TRIM( routine_name )
    130130
    131131    information_string_1 = 'Further information can be found at'
    132     IF(message_identifier(1:2) == 'NC') THEN
    133        information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc' // &
    134                               '/app/errmsg#NC'
     132    IF ( message_identifier(1:2) == 'NC' )  THEN
     133       information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc/app/errmsg#NC'
    135134    ELSE
    136        information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc' // &
    137                               '/app/errmsg#' // message_identifier
    138     ENDIF
    139 
    140 
    141 !
    142 !-- Output the output string and the corresponding message string which had
    143 !-- been already assigned in the calling subroutine.
     135       information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc/app/errmsg#' //      &
     136                              message_identifier
     137    ENDIF
     138
     139
     140!
     141!-- Output the output string and the corresponding message string which had been already assigned in
     142!-- the calling subroutine.
    144143!
    145144!-- First find out if output shall be done on this PE.
     
    210209       IF ( pe_out_of_range )  THEN
    211210          WRITE ( *, '(A)' )  '+++ WARNING from routine message:'
    212           WRITE ( *, '(A,I6,A)' )  '    PE ', output_on_pe, &
    213                                    ' choosed for output is larger '
    214           WRITE ( *, '(A,I6)' )  '    than the maximum number of used PEs', &
    215                                  numprocs-1
     211          WRITE ( *, '(A,I6,A)' )  '    PE ', output_on_pe, ' choosed for output is larger '
     212          WRITE ( *, '(A,I6)' )  '    than the maximum number of used PEs', numprocs-1
    216213          WRITE ( *, '(A)' )  '    Output is done on PE0 instead'
    217214       ENDIF
     
    224221       abort_mode = requested_action
    225222!
    226 !--    Since nested runs always use MPI_ABORT, let only the PE which output a message initiate
    227 !--    the abort. Others just wait.
     223!--    Since nested runs always use MPI_ABORT, let only the PE which output a message initiate the
     224!--    abort. Others just wait.
    228225       IF ( nested_run  .AND.  requested_action == 1  .AND.  .NOT. do_output )  THEN
    229226#if defined( __parallel )
     
    342339
    343340
    344 !------------------------------------------------------------------------------!
     341!--------------------------------------------------------------------------------------------------!
    345342! Description:
    346343! ------------
    347344!> Abort routine for failures durin reading of namelists
    348 !------------------------------------------------------------------------------!
     345!--------------------------------------------------------------------------------------------------!
    349346 SUBROUTINE parin_fail_message( location, line )
    350347
    351     USE control_parameters,                                                    &
     348    USE control_parameters,                                                                        &
    352349        ONLY:  message_string
    353350
     
    372369    ENDDO
    373370
    374  20 WRITE( message_string, '(A,I3,A)' )                                        &
    375                    'Error(s) in NAMELIST '// TRIM(location) //                 &
    376                    '&Reading fails on line ', line_counter,                    &
    377                    ' at&' // line
     371 20 WRITE( message_string, '(A,I3,A)' ) 'Error(s) in NAMELIST '// TRIM(location) //                &
     372                                        '&Reading fails on line ', line_counter, ' at&' // line
    378373    CALL message( 'parin', 'PA0271', 1, 2, 0, 6, 0 )
    379374
Note: See TracChangeset for help on using the changeset viewer.