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

    r3964 r3987  
    2525! -----------------
    2626! $Id$
     27! Introduce alternative switch for debug output during timestepping
     28!
     29! 3964 2019-05-09 09:48:32Z suehring
    2730! Ensure that veloctiy term in calculation of bulk Richardson number does not
    2831! become zero
     
    8588        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,  &
    8689               bc_dirichlet_s, dt_3d, dz, constant_diffusion,                  &
    87                debug_output, debug_string, humidity, initializing_actions,     &
     90               debug_output_timestep,                                          &
     91               humidity,                                                       &
     92               initializing_actions,                                           &
    8893               message_string, nesting_offline, neutral, passive_scalar,       &
    8994               rans_mode, rans_tke_e, time_since_reference_point, volume_flow
     
    167172       REAL(wp), DIMENSION(1:3) ::  volume_flow_l   !< local volume flow
    168173
    169 !
    170 !--    Debug location message
    171        IF ( debug_output )  THEN
    172           WRITE( debug_string, * ) 'nesting_offl_mass_conservation'
    173           CALL debug_message( debug_string, 'start' )
    174        ENDIF
    175        
     174
     175       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_mass_conservation', 'start' )
     176
    176177       CALL  cpu_log( log_point(58), 'offline nesting', 'start' )
    177178       
     
    249250       
    250251       CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
    251 !
    252 !--    Debug location message
    253        IF ( debug_output )  THEN
    254           WRITE( debug_string, * ) 'nesting_offl_mass_conservation'
    255           CALL debug_message( debug_string, 'end' )
    256        ENDIF
     252
     253       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_mass_conservation', 'end' )
    257254
    258255    END SUBROUTINE nesting_offl_mass_conservation
     
    287284       REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref_l  !< reference profile for v-component on subdomain
    288285       
    289 !
    290 !--    Debug location message
    291        IF ( debug_output )  THEN
    292           WRITE( debug_string, * ) 'nesting_offl_bc'
    293           CALL debug_message( debug_string, 'start' )
    294        ENDIF
     286
     287       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'start' )
    295288
    296289       CALL  cpu_log( log_point(58), 'offline nesting', 'start' )     
     
    828821   
    829822       CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
    830 !
    831 !--    Debug location message
    832        IF ( debug_output )  THEN
    833           WRITE( debug_string, * ) 'nesting_offl_bc'
    834           CALL debug_message( debug_string, 'end' )
    835        ENDIF
     823
     824       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'end' )
     825
    836826
    837827    END SUBROUTINE nesting_offl_bc
Note: See TracChangeset for help on using the changeset viewer.