Ignore:
Timestamp:
Apr 11, 2019 11:29:34 AM (5 years ago)
Author:
kanani
Message:

restructure/add location/debug messages

File:
1 edited

Legend:

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

    r3814 r3885  
    2525! -----------------
    2626! $Id$
     27! Changes related to global restructuring of location messages and introduction
     28! of additional debug messages
     29!
     30! 3814 2019-03-26 08:40:31Z pavelkrc
    2731! unused variables removed
    2832!
     
    258262
    259263    USE control_parameters,                                                    &
    260         ONLY:  do3d, do3d_no, do3d_time_count, io_blocks, io_group,            &
     264        ONLY:  debug_output, debug_string,                                     &
     265               do3d, do3d_no, do3d_time_count, io_blocks, io_group,            &
    261266               land_surface, message_string, ntdim_3d, nz_do3d, psolver,       &
    262267               time_since_reference_point, urban_surface, varnamelength
     
    335340!-- Return, if nothing to output
    336341    IF ( do3d_no(av) == 0 )  RETURN
     342
     343    IF ( debug_output )  THEN
     344       WRITE( debug_string, * ) 'data_output_3d'
     345       CALL debug_message( debug_string, 'start' )
     346    ENDIF
    337347
    338348    CALL cpu_log (log_point(14),'data_output_3d','start')
     
    866876    CALL cpu_log( log_point(14), 'data_output_3d', 'stop' )
    867877
     878    IF ( debug_output )  THEN
     879       WRITE( debug_string, * ) 'data_output_3d'
     880       CALL debug_message( debug_string, 'end' )
     881    ENDIF
     882
    868883 END SUBROUTINE data_output_3d
Note: See TracChangeset for help on using the changeset viewer.