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

    r3875 r3885  
    1515! PALM. If not, see <http://www.gnu.org/licenses/>.
    1616!
    17 ! Copyright 2009-2018 Carl von Ossietzky Universitaet Oldenburg
     17! Copyright 2009-2019 Carl von Ossietzky Universitaet Oldenburg
    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! 3875 2019-04-08 17:35:12Z knoop
    2832! Addaped wtm_tendency to fit the module actions interface
    2933!
     
    197201
    198202    USE control_parameters,                                                    &
    199         ONLY:  coupling_char, dt_3d, dz, message_string, simulated_time,       &
     203        ONLY:  coupling_char,                                                  &
     204               debug_output,                                                   &
     205               dt_3d, dz, message_string, simulated_time,                      &
    200206               wind_turbine, initializing_actions
    201207
     
    984990       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: index_nact       !<
    985991       
    986        CALL location_message( 'initializing wind turbine model', .FALSE. )
     992       IF ( debug_output )  CALL debug_message( 'wtm_init', 'start' )
    987993       
    988994       ALLOCATE( index_nacb(1:nturbines) )
     
    13411347       CALL wtm_read_blade_tables
    13421348
    1343        CALL location_message( 'finished', .TRUE. )
     1349       IF ( debug_output )  CALL debug_message( 'wtm_init', 'end' )
    13441350 
    13451351    END SUBROUTINE wtm_init
Note: See TracChangeset for help on using the changeset viewer.