Ignore:
Timestamp:
Mar 3, 2020 12:47:02 PM (4 years ago)
Author:
oliver.maas
Message:

Bugfix: shifted netcdf preprocessor directive to correct position

File:
1 edited

Legend:

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

    r4434 r4436  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! Bugfix: shifted netcdf preprocessor directive to correct position
    2424!
    2525! Former revisions:
     
    644644    SUBROUTINE wtm_check_parameters
    645645
    646    
    647646       IMPLICIT NONE
    648    
     647
    649648       IF ( .NOT. input_pids_wtm )  THEN
    650649          IF ( ( .NOT.speed_control ) .AND. pitch_control )  THEN
     
    653652             CALL message( 'wtm_check_parameters', 'PA0461', 1, 2, 0, 6, 0 )
    654653          ENDIF
    655          
     654
    656655          IF ( ANY( omega_rot(1:nturbines) < 0.0 ) )  THEN
    657656             message_string = 'omega_rot < 0.0, Please set omega_rot to '     // &
     
    659658             CALL message( 'wtm_check_parameters', 'PA0462', 1, 2, 0, 6, 0 )
    660659          ENDIF
    661          
    662          
     660
     661
    663662          IF ( ANY( rcx(1:nturbines) == 9999999.9_wp ) .OR.                       &
    664663                ANY( rcy(1:nturbines) == 9999999.9_wp ) .OR.                       &
     
    686685       REAL(wp) ::  delta_r_init     !<
    687686
     687#if defined( __netcdf )
    688688!
    689689! Read wtm input file (netcdf) if it exists
     
    692692!
    693693!--       Open the wtm  input file
    694 #if defined( __netcdf )
    695694          CALL open_read_file( TRIM( input_file_wtm ) //                       &
    696695                               TRIM( coupling_char ), pids_id )
Note: See TracChangeset for help on using the changeset viewer.