Ignore:
Timestamp:
May 22, 2019 9:52:13 AM (5 years ago)
Author:
kanani
Message:

clean up location, debug and error messages

File:
1 edited

Legend:

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

    r3885 r3987  
    2525! -----------------
    2626! $Id$
     27! Introduce alternative switch for debug output during timestepping
     28!
     29! 3885 2019-04-11 11:29:34Z kanani
    2730! Changes related to global restructuring of location messages and introduction
    2831! of additional debug messages
     
    262265
    263266    USE control_parameters,                                                    &
    264         ONLY:  debug_output, debug_string,                                     &
     267        ONLY:  debug_output_timestep,                                          &
    265268               do3d, do3d_no, do3d_time_count, io_blocks, io_group,            &
    266269               land_surface, message_string, ntdim_3d, nz_do3d, psolver,       &
     
    341344    IF ( do3d_no(av) == 0 )  RETURN
    342345
    343     IF ( debug_output )  THEN
    344        WRITE( debug_string, * ) 'data_output_3d'
    345        CALL debug_message( debug_string, 'start' )
    346     ENDIF
     346    IF ( debug_output_timestep )  CALL debug_message( 'data_output_3d', 'start' )
    347347
    348348    CALL cpu_log (log_point(14),'data_output_3d','start')
     
    876876    CALL cpu_log( log_point(14), 'data_output_3d', 'stop' )
    877877
    878     IF ( debug_output )  THEN
    879        WRITE( debug_string, * ) 'data_output_3d'
    880        CALL debug_message( debug_string, 'end' )
    881     ENDIF
     878    IF ( debug_output_timestep )  CALL debug_message( 'data_output_3d', 'end' )
     879
    882880
    883881 END SUBROUTINE data_output_3d
Note: See TracChangeset for help on using the changeset viewer.