source: palm/trunk/SOURCE/message.f90 @ 4578

Last change on this file since 4578 was 4578, checked in by gronemeier, 4 years ago

message.f90:

  • bugfix : do not save input values from last call of routines debug_message and location_message
  • changes: layout changes according to PALM coding standards

time_integration.f90:

  • bugfix: removed unused variables
  • Property svn:keywords set to Id
File size: 13.9 KB
RevLine 
[1682]1!> @file message.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[2000]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.
[1036]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/>.
16!
[4360]17! Copyright 1997-2020 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[213]21! -----------------
[4578]22!
23!
[1321]24! Former revisions:
25! -----------------
26! $Id: message.f90 4578 2020-06-25 15:43:32Z gronemeier $
[4578]27! bugfix : do not save input values from last call of routines debug_message and location_message
28! changes: layout changes according to PALM coding standards
29!
30! 4536 2020-05-17 17:24:13Z raasch
[4536]31! location message format changed
[4578]32!
[4536]33! 4360 2020-01-07 11:25:50Z suehring
[4182]34! Corrected "Former revisions" section
[4578]35!
[4182]36! 4097 2019-07-15 11:59:11Z suehring
[4097]37! Avoid overlong lines - limit is 132 characters per line
[4578]38!
[4097]39! 3987 2019-05-22 09:52:13Z kanani
[3987]40! Improved formatting of job logfile output,
41! changed output of DEBUG file
[4578]42!
[3987]43! 3885 2019-04-11 11:29:34Z kanani
[4578]44! Changes related to global restructuring of location messages and introduction
[3885]45! of additional debug messages
[4578]46!
[3885]47! 3655 2019-01-07 16:51:22Z knoop
[3248]48! Minor formating changes
[1321]49!
[4182]50! 213 2008-11-13 10:26:18Z raasch
51! Initial revision
52!
[213]53! Description:
54! ------------
[1682]55!> Handling of the different kinds of messages.
56!> Meaning of formal parameters:
57!> requested_action: 0 - continue, 1 - abort by stop, 2 - abort by mpi_abort
[1764]58!>                   3 - abort by mpi_abort using MPI_COMM_WORLD
[1682]59!> message_level: 0 - informative, 1 - warning, 2 - error
60!> output_on_pe: -1 - all, else - output on specified PE
61!> file_id: 6 - stdout (*)
[1808]62!> flush_file: 0 - no action, 1 - flush the respective output buffer
[213]63!------------------------------------------------------------------------------!
[1682]64 SUBROUTINE message( routine_name, message_identifier, requested_action, &
[1808]65                     message_level, output_on_pe, file_id, flush_file )
[4578]66
[1384]67    USE control_parameters,                                                    &
[1320]68        ONLY:  abort_mode, message_string
69
70    USE kinds
71
[213]72    USE pegrid
73
[1764]74    USE pmc_interface,                                                         &
75        ONLY:  cpl_id, nested_run
76
[213]77    IMPLICIT NONE
78
[1682]79    CHARACTER(LEN=6)   ::  message_identifier            !<
[1764]80    CHARACTER(LEN=20)  ::  nest_string                   !< nest id information
[1682]81    CHARACTER(LEN=*)   ::  routine_name                  !<
82    CHARACTER(LEN=200) ::  header_string                 !<
[3987]83    CHARACTER(LEN=200) ::  header_string_2               !< for message ID and routine name
[1682]84    CHARACTER(LEN=200) ::  information_string_1          !<
85    CHARACTER(LEN=200) ::  information_string_2          !<
[213]86
[1682]87    INTEGER(iwp) ::  file_id                             !<
[1808]88    INTEGER(iwp) ::  flush_file                          !<
[1682]89    INTEGER(iwp) ::  i                                   !<
90    INTEGER(iwp) ::  message_level                       !<
91    INTEGER(iwp) ::  output_on_pe                        !<
92    INTEGER(iwp) ::  requested_action                    !<
[213]93
[1682]94    LOGICAL ::  do_output                                !<
95    LOGICAL ::  pe_out_of_range                          !<
[213]96
97
98    do_output       = .FALSE.
99    pe_out_of_range = .FALSE.
100
101!
[1764]102!-- In case of nested runs create the nest id informations
103    IF ( nested_run )  THEN
104       WRITE( nest_string, '(1X,A,I2.2)' )  'from nest-id ', cpl_id
105    ELSE
106       nest_string = ''
107    ENDIF
108!
[213]109!-- Create the complete output string, starting with the message level
110    IF ( message_level == 0 )  THEN
[1764]111       header_string = '--- informative message' // TRIM(nest_string) //       &
[3987]112                       ' ---'
[213]113    ELSEIF ( message_level == 1 )  THEN
[3987]114       header_string = '+++ warning message' // TRIM(nest_string) // ' ---'
[213]115    ELSEIF ( message_level == 2 )  THEN
[3987]116       header_string = '+++ error message' // TRIM(nest_string) // ' ---'
[213]117    ELSE
[1764]118       WRITE( header_string,'(A,I2)' )  '+++ unknown message level' //         &
119                                        TRIM(nest_string) // ': ',             &
[213]120                                        message_level
121    ENDIF
122
123!
124!-- Add the message identifier and the generating routine
[3987]125    header_string_2 = 'ID: ' // message_identifier // &
126                      '  generated by routine: ' // TRIM( routine_name )
[4578]127
[311]128    information_string_1 = 'Further information can be found at'
129    IF(message_identifier(1:2) == 'NC') THEN
[1664]130       information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc' // &
[563]131                              '/app/errmsg#NC'
[311]132    ELSE
[1664]133       information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc' // &
[563]134                              '/app/errmsg#' // message_identifier
[1764]135    ENDIF
[213]136
[4578]137
[213]138!
139!-- Output the output string and the corresponding message string which had
140!-- been already assigned in the calling subroutine.
141!
142!-- First find out if output shall be done on this PE.
143    IF ( output_on_pe == -1 )  THEN
144       do_output = .TRUE.
145    ELSEIF ( myid == output_on_pe )  THEN
146       do_output = .TRUE.
147    ENDIF
148#if defined( __parallel )
149!
150!-- In case of illegal pe number output on pe0
151    IF ( output_on_pe > numprocs-1 )  THEN
152       pe_out_of_range = .TRUE.
153       IF ( myid == 0 )  do_output = .TRUE.
154    ENDIF
155#endif
156
157!
158!-- Now do the output
159    IF ( do_output )  THEN
[1402]160
[213]161       IF ( file_id == 6 )  THEN
162!
163!--       Output on stdout
[3987]164          WRITE( *, '(16X,A)' )  TRIM( header_string )
165          WRITE( *, '(20X,A)' )  TRIM( header_string_2 )
[213]166!
167!--       Cut message string into pieces and output one piece per line.
168!--       Remove leading blanks.
169          message_string = ADJUSTL( message_string )
170          i = INDEX( message_string, '&' )
171          DO WHILE ( i /= 0 )
[3987]172             WRITE( *, '(20X,A)' )  ADJUSTL( message_string(1:i-1) )
[213]173             message_string = ADJUSTL( message_string(i+1:) )
174             i = INDEX( message_string, '&' )
175          ENDDO
[3987]176          WRITE( *, '(20X,A)' )  ''
177          WRITE( *, '(20X,A)' )  TRIM( message_string )
178          WRITE( *, '(20X,A)' )  ''
[4578]179          WRITE( *, '(20X,A)' )  TRIM( information_string_1 )
180          WRITE( *, '(20X,A)' )  TRIM( information_string_2 )
[3987]181          WRITE( *, '(20X,A)' )  ''
[213]182
183       ELSE
184!
185!--       Output on requested file id (file must have been opened elsewhere!)
186          WRITE( file_id, '(A/)' )  TRIM( header_string )
187!
188!--       Cut message string into pieces and output one piece per line.
189!--       Remove leading blanks.
190          message_string = ADJUSTL( message_string )
191          i = INDEX( message_string, '&' )
192          DO WHILE ( i /= 0 )
193             WRITE( file_id, '(4X,A)' )  ADJUSTL( message_string(1:i-1) )
194             message_string = ADJUSTL( message_string(i+1:) )
195             i = INDEX( message_string, '&' )
196          ENDDO
197          WRITE( file_id, '(4X,A)' )  TRIM( message_string )
[335]198          WRITE( file_id, '(4X,A)' )  ''
[4578]199          WRITE( file_id, '(4X,A)' )  TRIM( information_string_1 )
200          WRITE( file_id, '(4X,A)' )  TRIM( information_string_2 )
[335]201          WRITE( file_id, '(4X,A)' )  ''
[213]202!
203!--       Flush buffer, if requested
[1808]204          IF ( flush_file == 1 )  FLUSH( file_id )
[213]205       ENDIF
206
207       IF ( pe_out_of_range )  THEN
[226]208          WRITE ( *, '(A)' )  '+++ WARNING from routine message:'
[213]209          WRITE ( *, '(A,I6,A)' )  '    PE ', output_on_pe, &
210                                   ' choosed for output is larger '
211          WRITE ( *, '(A,I6)' )  '    than the maximum number of used PEs', &
212                                 numprocs-1
213          WRITE ( *, '(A)' )  '    Output is done on PE0 instead'
214       ENDIF
215
216    ENDIF
217
218!
219!-- Abort execution, if requested
220    IF ( requested_action > 0 )  THEN
221       abort_mode = requested_action
222       CALL local_stop
223    ENDIF
224
[226]225 END SUBROUTINE message
[1384]226
227
[3885]228!--------------------------------------------------------------------------------------------------!
[1384]229! Description:
230! ------------
[1682]231!> Prints out the given location on stdout
[3885]232!--------------------------------------------------------------------------------------------------!
233 SUBROUTINE location_message( location, message_type )
[1384]234
[3885]235    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                                            &
[1764]236        ONLY:  OUTPUT_UNIT
[1402]237
[4578]238    USE pegrid,                                                                                    &
239        ONLY:  myid
[1384]240
[3885]241    USE pmc_interface,                                                                             &
[3241]242        ONLY:  cpl_id
[1764]243
[1384]244    IMPLICIT NONE
245
[4578]246    CHARACTER(LEN=*)  ::  location             !< text to be output on stdout
247    CHARACTER(LEN=60) ::  location_trimmed     !< trimmed text to be output on stdout
248    CHARACTER(LEN=*)  ::  message_type         !< type of message; supported values: 'start', 'finished'
249    CHARACTER(LEN=10) ::  message_type_string  !< formatted message-type string for output
250    CHARACTER(LEN=8)  ::  system_time          !< formatted system clock time
251    CHARACTER(LEN=10) ::  time                 !< current time of system
252
[1764]253!
254!-- Output for nested runs only on the root domain
255    IF ( cpl_id /= 1 )  RETURN
[1384]256
257    IF ( myid == 0 )  THEN
[3885]258!
259!--    Get system time for debug info output (helpful to estimate the required computing time for
[4578]260!--    specific parts of code)
[3885]261       CALL date_and_time( TIME=time )
[4578]262       system_time = time(1:2) // ':' // time(3:4) // ':' // time(5:6)
[3885]263!
[4578]264!--    Write message-type string depending on message_type
265       message_type_string = REPEAT( '-', 10 )
266       IF ( TRIM( message_type ) == 'start' )                                                      &
267          message_type_string(2:) = TRIM( message_type ) // '----'
268       IF ( TRIM( message_type ) == 'finished' )                                                   &
269          message_type_string(2:) = TRIM( message_type ) // '-'
[3885]270!
[4578]271!--    Trim location text to a maximum of 60 chars
272!--    Note: if the length is set within the write format, the string is right-aligned; to trim and
273!--    left-align the output, we need to use this detour
274       WRITE( location_trimmed, '(A)' )  ADJUSTL( TRIM( location ) )
[3987]275!
[3885]276!--    Write and flush debug location or info message to file
[4578]277       WRITE( OUTPUT_UNIT, 200 )  system_time, message_type_string, TRIM( location_trimmed )
[1808]278       FLUSH( OUTPUT_UNIT )
[3885]279!
280!--    Message formats
[4578]281200    FORMAT ( 3X, A, 3x, A, 3X, A )
[3885]282
[1384]283    ENDIF
284
285 END SUBROUTINE location_message
[3246]286
287
[3885]288!--------------------------------------------------------------------------------------------------!
289! Description:
290! ------------
291!> Prints out the given debug information to unit 9 (DEBUG files in temporary directory)
292!> for each PE on each domain.
293!--------------------------------------------------------------------------------------------------!
294 SUBROUTINE debug_message( debug_string, message_type )
295
296    USE control_parameters,                                                                        &
[3987]297        ONLY:  time_since_reference_point
[3885]298
299    IMPLICIT NONE
300
[4578]301    CHARACTER(LEN=*)  ::  debug_string         !< debug message to be output to debug_output_unit
302    CHARACTER(LEN=*)  ::  message_type         !< type of message; supported values: 'start', 'end', 'info'
303    CHARACTER(LEN=7)  ::  message_type_string  !< formatted message-type string for output
304    CHARACTER(LEN=8)  ::  system_time          !< formatted system clock time
305    CHARACTER(LEN=10) ::  time                 !< current time of system
[3885]306
307    INTEGER, PARAMETER ::  debug_output_unit = 9
308
309!
310!-- Get system time for debug info output (helpful to estimate the required computing time for
[4578]311!-- specific parts of code)
[3885]312    CALL date_and_time( TIME=time )
[4578]313    system_time = time(1:2) // ':' // time(3:4) // ':' // time(5:6)
[3885]314!
[4578]315!-- Write message-type string depending on message_type
316    message_type_string = REPEAT( '-', 7 )
317    IF ( TRIM( message_type ) == 'start' )  message_type_string(2:) = TRIM( message_type ) // '-'
318    IF ( TRIM( message_type ) == 'end' )    message_type_string(2:) = TRIM( message_type ) // '---'
319    IF ( TRIM( message_type ) == 'info' )   message_type_string(2:) = TRIM( message_type ) // '--'
[3885]320!
321!-- Write and flush debug location or info message to file
[4578]322    WRITE( debug_output_unit, 201 )    system_time, time_since_reference_point, &
323                                       message_type_string, TRIM( debug_string )
[3885]324    FLUSH( debug_output_unit )
325!
326!-- Message formats
[3987]327201 FORMAT ( 'System time: ', A, ' | simulated time (s): ', F12.3, ' | ', A, ' ', A )
[3885]328
329 END SUBROUTINE debug_message
330
331
[3246]332!------------------------------------------------------------------------------!
333! Description:
334! ------------
[3247]335!> Abort routine for failures durin reading of namelists
[3246]336!------------------------------------------------------------------------------!
337 SUBROUTINE parin_fail_message( location, line )
338
339    USE control_parameters,                                                    &
340        ONLY:  message_string
341
[3247]342    USE kinds
343
[3246]344    IMPLICIT NONE
345
346    CHARACTER(LEN=*) ::  location !< text to be output on stdout
347    CHARACTER(LEN=*) ::  line
348
[3247]349    CHARACTER(LEN=80) ::  line_dum
350
351    INTEGER(iwp) ::  line_counter
352
353    line_dum = ' '
354    line_counter = 0
355
356    REWIND( 11 )
[3248]357    DO WHILE ( INDEX( line_dum, TRIM(line) ) == 0 )
358       READ ( 11, '(A)', END=20 )  line_dum
359       line_counter = line_counter + 1
[3247]360    ENDDO
361
362 20 WRITE( message_string, '(A,I3,A)' )                                        &
363                   'Error(s) in NAMELIST '// TRIM(location) //                 &
364                   '&Reading fails on line ', line_counter,                    &
365                   ' at&' // line
[3248]366    CALL message( 'parin', 'PA0271', 1, 2, 0, 6, 0 )
[3246]367
368 END SUBROUTINE parin_fail_message
Note: See TracBrowser for help on using the repository browser.