Ignore:
Timestamp:
May 2, 2014 2:31:06 PM (10 years ago)
Author:
raasch
Message:

output of location messages to stdout

File:
1 edited

Legend:

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

    r1321 r1384  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! routine location_message added
    2424!
    2525! Former revisions:
     
    5151!------------------------------------------------------------------------------!
    5252
    53     USE control_parameters,                                                  &
     53    USE control_parameters,                                                    &
    5454        ONLY:  abort_mode, message_string
    5555
     
    206206
    207207 END SUBROUTINE message
     208
     209
     210 SUBROUTINE location_message( location )
     211
     212!------------------------------------------------------------------------------!
     213! Description:
     214! ------------
     215! Prints out the given location on stdout
     216!------------------------------------------------------------------------------!
     217
     218    USE pegrid,                                                                &
     219        ONLY :  myid
     220
     221    IMPLICIT NONE
     222
     223    CHARACTER(LEN=*) ::  location
     224
     225
     226    IF ( myid == 0 )  THEN
     227       WRITE ( 6, '(6X,''... '',A)' )  TRIM( location )
     228       CALL local_flush( 6 )
     229    ENDIF
     230
     231 END SUBROUTINE location_message
Note: See TracChangeset for help on using the changeset viewer.