Ignore:
Timestamp:
Feb 28, 2016 12:45:19 PM (8 years ago)
Author:
raasch
Message:

update of the nested domain system + some bugfixes

File:
1 edited

Legend:

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

    r1683 r1764  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! nest id added to header string, add linefeed to stdout to get messages better
     22! seperatedvfrom the location messages,
     23! in case of nested runs, location messages are given only by the root domain
    2224!
    2325! Former revisions:
     
    5557!> Meaning of formal parameters:
    5658!> requested_action: 0 - continue, 1 - abort by stop, 2 - abort by mpi_abort
     59!>                   3 - abort by mpi_abort using MPI_COMM_WORLD
    5760!> message_level: 0 - informative, 1 - warning, 2 - error
    5861!> output_on_pe: -1 - all, else - output on specified PE
     
    6366                     message_level, output_on_pe, file_id, flush )
    6467 
    65 
    6668    USE control_parameters,                                                    &
    6769        ONLY:  abort_mode, message_string
     
    7173    USE pegrid
    7274
     75    USE pmc_interface,                                                         &
     76        ONLY:  cpl_id, nested_run
     77
    7378    IMPLICIT NONE
    7479
    7580    CHARACTER(LEN=6)   ::  message_identifier            !<
     81    CHARACTER(LEN=20)  ::  nest_string                   !< nest id information
    7682    CHARACTER(LEN=*)   ::  routine_name                  !<
    7783    CHARACTER(LEN=200) ::  header_string                 !<
     
    94100
    95101!
     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!
    96109!-- Create the complete output string, starting with the message level
    97110    IF ( message_level == 0 )  THEN
    98        header_string = '--- informative message ---  ID:'
     111       header_string = '--- informative message' // TRIM(nest_string) //       &
     112                       ' ---  ID:'
    99113    ELSEIF ( message_level == 1 )  THEN
    100        header_string = '+++ warning message ---  ID:'
     114       header_string = '+++ warning message' // TRIM(nest_string) // ' ---  ID:'
    101115    ELSEIF ( message_level == 2 )  THEN
    102        header_string = '+++ error message ---  ID:'
     116       header_string = '+++ error message' // TRIM(nest_string) // ' ---  ID:'
    103117    ELSE
    104        WRITE( header_string,'(A,I2)' )  '+++ unknown message level: ', &
     118       WRITE( header_string,'(A,I2)' )  '+++ unknown message level' //         &
     119                                        TRIM(nest_string) // ': ',             &
    105120                                        message_level
    106121    ENDIF
     
    118133       information_string_2 = 'http://palm.muk.uni-hannover.de/trac/wiki/doc' // &
    119134                              '/app/errmsg#' // message_identifier
    120     END IF
     135    ENDIF
    121136   
    122137
     
    147162!
    148163!--       Output on stdout
    149           WRITE( *, '(A/)' )  TRIM( header_string )
     164          WRITE( *, '(//A/)' )  TRIM( header_string )
    150165!
    151166!--       Cut message string into pieces and output one piece per line.
     
    219234
    220235    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                        &
    221         ONLY :  OUTPUT_UNIT
     236        ONLY:  OUTPUT_UNIT
    222237
    223238    USE pegrid,                                                                &
    224         ONLY :  myid
     239        ONLY:  myid
     240
     241    USE pmc_interface,                                                         &
     242        ONLY:  cpl_id
    225243
    226244    IMPLICIT NONE
     
    229247    LOGICAL          ::  advance  !< switch for advancing/noadvancing I/O
    230248
     249!
     250!-- Output for nested runs only on the root domain
     251    IF ( cpl_id /= 1 )  RETURN
    231252
    232253    IF ( myid == 0 )  THEN
Note: See TracChangeset for help on using the changeset viewer.