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_2d.f90

    r3943 r3987  
    2525! -----------------
    2626! $Id$
     27! Introduce alternative switch for debug output during timestepping
     28!
     29! 3943 2019-05-02 09:50:41Z maronga
    2730! Added output of qsws for green roofs.
    2831!
     
    306309        ONLY:  data_output_2d_on_each_pe,                                      &
    307310               data_output_xy, data_output_xz, data_output_yz,                 &
    308                debug_output, debug_string,                                     &
     311               debug_output_timestep,                                          &
    309312               do2d,                                                           &
    310313               do2d_xy_last_time, do2d_xy_time_count,                          &
     
    404407
    405408
    406     IF ( debug_output )  THEN
    407        WRITE( debug_string, * ) 'data_output_2d'
    408        CALL debug_message( debug_string, 'start' )
    409     ENDIF
     409    IF ( debug_output_timestep )  CALL debug_message( 'data_output_2d', 'start' )
    410410!
    411411!-- Immediate return, if no output is requested (no respective sections
     
    22842284    CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
    22852285
    2286     IF ( debug_output )  THEN
    2287        WRITE( debug_string, * ) 'data_output_2d'
    2288        CALL debug_message( debug_string, 'end' )
    2289     ENDIF
     2286    IF ( debug_output_timestep )  CALL debug_message( 'data_output_2d', 'end' )
     2287
    22902288
    22912289 END SUBROUTINE data_output_2d
Note: See TracChangeset for help on using the changeset viewer.