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

    r3753 r3885  
    2727! -----------------
    2828! $Id$
     29! Changes related to global restructuring of location messages and introduction
     30! of additional debug messages
     31!
     32! 3753 2019-02-19 14:48:54Z dom_dwd_user
    2933! - Added automatic setting of mrt_nlevels in case it was not part of
    3034! radiation_parameters namelist (or set to 0 accidentially).
     
    150154
    151155    USE control_parameters,                                                    &
    152         ONLY:  average_count_3d, biometeorology, dz, dz_stretch_factor,        &
     156        ONLY:  average_count_3d, biometeorology,                               &
     157               debug_output,                                                   &
     158               dz, dz_stretch_factor,                                          &
    153159               dz_stretch_level, humidity, initializing_actions, nz_do3d,      &
    154160               surface_pressure
     
    12091215    REAL ( wp )  :: height  !< current height in meters
    12101216
    1211     CALL location_message( 'initializing biometeorology module', .FALSE. )
     1217    IF ( debug_output )  CALL debug_message( 'bio_init', 'start' )
    12121218!
    12131219!-- Determine cell level corresponding to 1.1 m above ground level
     
    12291235    IF ( uv_exposure )  CALL netcdf_data_input_uvem
    12301236
    1231     CALL location_message( 'finished', .TRUE. )
     1237    IF ( debug_output )  CALL debug_message( 'bio_init', 'end' )
    12321238
    12331239 END SUBROUTINE bio_init
Note: See TracChangeset for help on using the changeset viewer.