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/surface_layer_fluxes_mod.f90

    r3885 r3987  
    2626! -----------------
    2727! $Id$
     28! Introduce alternative switch for debug output during timestepping
     29!
     30! 3885 2019-04-11 11:29:34Z kanani
    2831! Changes related to global restructuring of location messages and introduction
    2932! of additional debug messages
     
    278281               constant_heatflux, constant_scalarflux,                         &
    279282               constant_waterflux, coupling_mode,                              &
    280                debug_output, debug_string,                                     &
     283               debug_output_timestep,                                          &
    281284               do_output_at_2m, humidity,                                      &
    282285               ibc_e_b, ibc_pt_b, indoor_model, initializing_actions,          &
     
    364367
    365368
    366        IF ( debug_output )  CALL debug_message( 'surface_layer_fluxes', 'start' )
     369       IF ( debug_output_timestep )  CALL debug_message( 'surface_layer_fluxes', 'start' )
    367370
    368371       surf_vertical = .FALSE. !< flag indicating vertically orientated surface elements
     
    726729       mom_tke = .FALSE.
    727730
    728        IF ( debug_output )  CALL debug_message( 'surface_layer_fluxes', 'end' )
     731       IF ( debug_output_timestep )  CALL debug_message( 'surface_layer_fluxes', 'end' )
    729732
    730733    END SUBROUTINE surface_layer_fluxes
Note: See TracChangeset for help on using the changeset viewer.