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

restructure/add location/debug messages

File:
1 edited

Legend:

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

    r3876 r3885  
    1515! PALM. If not, see <http://www.gnu.org/licenses/>.
    1616!
    17 ! Copyright 2018-2018 University of Helsinki
     17! Copyright 2018-2019 University of Helsinki
    1818! Copyright 1997-2019 Leibniz Universitaet Hannover
    1919!--------------------------------------------------------------------------------!
     
    2626! -----------------
    2727! $Id$
     28! Changes related to global restructuring of location messages and introduction
     29! of additional debug messages
     30!
     31! 3876 2019-04-08 18:41:49Z knoop
    2832! Introduced salsa_actions module interface
    2933!
     
    12901294    INTEGER(iwp) :: j   !<
    12911295
    1292     CALL location_message( 'initializing salsa (sectional aerosol module )', .TRUE. )
     1296    IF ( debug_output )  CALL debug_message( 'salsa_init', 'start' )
    12931297
    12941298    bin_low_limits = 0.0_wp
     
    14391443    ENDIF
    14401444
    1441     CALL location_message( 'finished', .TRUE. )
     1445    IF ( debug_output )  CALL debug_message( 'salsa_init', 'end' )
    14421446
    14431447 END SUBROUTINE salsa_init
     
    80878091!
    80888092!--          Subrange 2b:
     8093!--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log,
     8094!--          and actually, aerosol_flux_mass_fracs_b is not used anywhere else except for this message,
     8095!--          hence, what do we need it for?
    80898096             IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp )  THEN
    8090                 CALL location_message( '   salsa_emission_setup: emissions are soluble!', .TRUE. )
     8097                CALL debug_message( '   salsa_emission_setup: emissions are soluble!', 'info' )
    80918098             ENDIF
    80928099
     
    86818688!
    86828689!--    Subrange 2b:
    8683        IF ( .NOT. no_insoluble )  THEN
    8684           CALL location_message( '    salsa_mass_flux: All emissions are soluble!', .TRUE. )
    8685        ENDIF
     8690!--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log
     8691!        IF ( .NOT. no_insoluble )  THEN
     8692!           CALL location_message( '    salsa_mass_flux: All emissions are soluble!', .TRUE. )
     8693!        ENDIF
    86868694
    86878695    END SUBROUTINE set_mass_flux
     
    87768784          END SELECT
    87778785       ENDDO
    8778        IF ( SUM( emission_index_chem ) == 0 )  THEN
    8779           CALL location_message( '    salsa_gas_emission_setup: no gas emissions', .TRUE. )
    8780        ENDIF
     8786!--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log
     8787!        IF ( SUM( emission_index_chem ) == 0 )  THEN
     8788!           CALL location_message( '    salsa_gas_emission_setup: no gas emissions', .TRUE. )
     8789!        ENDIF
    87818790!
    87828791!--    Inquire the fill value
Note: See TracChangeset for help on using the changeset viewer.