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

    r3831 r3885  
    1515! PALM. If not, see <http://www.gnu.org/licenses/>.
    1616!
    17 ! Copyright 2018-2018 Leibniz Universitaet Hannover
    18 ! Copyright 2018-2018 Freie Universitaet Berlin
    19 ! Copyright 2018-2018 Karlsruhe Institute of Technology
     17! Copyright 2018-2019 Leibniz Universitaet Hannover
     18! Copyright 2018-2019 Freie Universitaet Berlin
     19! Copyright 2018-2019 Karlsruhe Institute of Technology
    2020!--------------------------------------------------------------------------------!
    2121!
     
    2727! -----------------
    2828! $Id$
     29! Changes related to global restructuring of location messages and introduction
     30! of additional debug messages
     31!
     32! 3831 2019-03-28 09:11:22Z forkel
    2933! added nvar to USE chem_gasphase_mod (chem_modules will not include nvar anymore)
    3034!
     
    112116
    113117    USE control_parameters,                                                    &
    114         ONLY:  end_time, message_string, initializing_actions,                 &
     118        ONLY:  debug_output,                                                   &
     119               end_time, message_string, initializing_actions,                 &
    115120               intermediate_timestep_count, dt_3d
    116121 
     
    248253
    249254
    250     CALL location_message( 'Matching input emissions and model chemistry species', .FALSE. )
     255    IF ( debug_output )  CALL debug_message( 'chem_emissions_match', 'start' )
    251256
    252257    !
     
    696701       END SELECT
    697702
     703       IF ( debug_output )  CALL debug_message( 'chem_emissions_match', 'end' )
     704
    698705 END SUBROUTINE chem_emissions_match
    699706
     
    728735
    729736
    730   CALL location_message( 'Starting initialization of emission arrays', .FALSE. )
     737  IF ( debug_output )  CALL debug_message( 'chem_emissions_init', 'start' )
    731738
    732739  !
     
    802809
    803810  ENDIF   
     811
     812  IF ( debug_output )  CALL debug_message( 'chem_emissions_init', 'end' )
    804813
    805814 END SUBROUTINE chem_emissions_init
Note: See TracChangeset for help on using the changeset viewer.