Ignore:
Timestamp:
Oct 19, 2017 3:36:10 PM (7 years ago)
Author:
Giersch
Message:

Restart runs with the usage of the wind turbine model are possible now. Further small at reading/writing restart data

File:
1 edited

Legend:

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

    r2553 r2563  
    2626! -----------------
    2727! $Id$
     28! Restart runs with wind turbine model are possible now. For this purpose, two
     29! new subroutines wtm_write_restart_data and wtm_read_restart_data had to be
     30! defined
     31!
     32! 2553 2017-10-18 08:03:45Z Giersch
    2833! Bugfix of vertical loop in wtm_tendencies to account for different turbine
    2934! heights, bugfix of the interpolation of the u-component concerning the
     
    104109
    105110    USE control_parameters,                                                    &
    106         ONLY:  dt_3d, dz, message_string, simulated_time
     111        ONLY:  dt_3d, dz, message_string, simulated_time, wind_turbine,        &
     112               initializing_actions
    107113
    108114    USE cpulog,                                                                &
     
    124130
    125131    PRIVATE
    126 
    127     LOGICAL ::  wind_turbine=.FALSE.   !< switch for use of wind turbine model
    128132
    129133!
     
    265269    REAL(wp), DIMENSION(:), ALLOCATABLE ::  alpha_attack !<
    266270    REAL(wp), DIMENSION(:), ALLOCATABLE ::  chord        !<
    267     REAL(wp), DIMENSION(:), ALLOCATABLE ::  omega_gen    !< curr. generator speed
    268271    REAL(wp), DIMENSION(:), ALLOCATABLE ::  phi_rel      !<
    269     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pitch_add_old!<
    270272    REAL(wp), DIMENSION(:), ALLOCATABLE ::  torque_total !<
    271273    REAL(wp), DIMENSION(:), ALLOCATABLE ::  thrust_rotor !<
     
    337339    REAL(wp) ::  vs_sysp             !<
    338340    REAL(wp) ::  lp_coeff            !< coeff for the controller low pass filter
    339    
    340     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_old   !< last gen. speed
    341     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_f     !< filtered gen. sp
    342     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_f_old !< last filt. gen. sp
    343     REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_gen      !< generator torque
    344     REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_gen_old  !< last gen. torque
    345341
    346342    REAL(wp), DIMENSION(100) :: omega_rot_l = 0.0_wp !< local rot speed [rad/s]
     343
    347344!
    348345!-- Fixed variables for the yaw controller
     
    362359    INTEGER(iwp)                          ::  WDSHO            !<
    363360
     361!
     362!-- Variables that have to be saved in the binary file for restarts
     363    REAL(wp), DIMENSION(1:100) ::  pitch_add_old           = 0.0_wp  !< old constant pitch angle
     364    REAL(wp), DIMENSION(1:100) ::  omega_gen               = 0.0_wp  !< curr. generator speed
     365    REAL(wp), DIMENSION(1:100) ::  omega_gen_f             = 0.0_wp  !< filtered generator speed
     366    REAL(wp), DIMENSION(1:100) ::  omega_gen_old           = 0.0_wp  !< last generator speed
     367    REAL(wp), DIMENSION(1:100) ::  omega_gen_f_old         = 0.0_wp  !< last filtered generator speed
     368    REAL(wp), DIMENSION(1:100) ::  torque_gen              = 0.0_wp  !< generator torque
     369    REAL(wp), DIMENSION(1:100) ::  torque_gen_old          = 0.0_wp  !< last generator torque
     370
    364371
    365372    SAVE
     
    369376       MODULE PROCEDURE wtm_parin
    370377    END INTERFACE wtm_parin
     378
     379    INTERFACE wtm_write_restart_data
     380       MODULE PROCEDURE wtm_write_restart_data
     381    END INTERFACE wtm_write_restart_data
     382
     383    INTERFACE wtm_read_restart_data
     384       MODULE PROCEDURE wtm_read_restart_data
     385    END INTERFACE wtm_read_restart_data
    371386   
    372387    INTERFACE wtm_check_parameters
     
    410425   
    411426    PUBLIC wtm_check_parameters, wtm_forces, wtm_init, wtm_init_arrays,        &
    412            wtm_parin, wtm_tendencies, wind_turbine
     427           wtm_parin, wtm_write_restart_data, wtm_tendencies
     428
    413429
    414430 CONTAINS
     
    467483       wind_turbine = .TRUE.
    468484
     485       IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     486          CALL wtm_read_restart_data
     487       ENDIF
     488
    469489 10    CONTINUE   ! TBD Change from continue, mit ierrn machen
    470490
     
    472492    END SUBROUTINE wtm_parin
    473493
     494
     495!------------------------------------------------------------------------------!
     496! Description:
     497! ------------
     498!> This routine writes the respective restart data.
     499!------------------------------------------------------------------------------!
     500    SUBROUTINE wtm_write_restart_data 
     501
     502       IMPLICIT NONE
     503       
     504       WRITE ( 14 )  'omega_gen                     '
     505       WRITE ( 14 )  omega_gen
     506       WRITE ( 14 )  'omega_gen_f                   '
     507       WRITE ( 14 )  omega_gen_f
     508       WRITE ( 14 )  'omega_gen_f_old               '
     509       WRITE ( 14 )  omega_gen_f_old
     510       WRITE ( 14 )  'omega_gen_old                 '
     511       WRITE ( 14 )  omega_gen_old
     512       WRITE ( 14 )  'omega_rot                     '
     513       WRITE ( 14 )  omega_rot
     514       WRITE ( 14 )  'phi_yaw                       '
     515       WRITE ( 14 )  phi_yaw(:)
     516       WRITE ( 14 )  'pitch_add                     '
     517       WRITE ( 14 )  pitch_add
     518       WRITE ( 14 )  'pitch_add_old                 '
     519       WRITE ( 14 )  pitch_add_old
     520       WRITE ( 14 )  'torque_gen                    '
     521       WRITE ( 14 )  torque_gen
     522       WRITE ( 14 )  'torque_gen_old                '
     523       WRITE ( 14 )  torque_gen_old
     524     
     525       WRITE ( 14 )  '*** end wtm ***               '
     526       
     527    END SUBROUTINE wtm_write_restart_data   
     528
     529
     530!------------------------------------------------------------------------------!
     531! Description:
     532! ------------
     533!> This routine reads the respective restart data.
     534!------------------------------------------------------------------------------!
     535 SUBROUTINE wtm_read_restart_data
     536
     537
     538    IMPLICIT NONE
     539
     540    CHARACTER (LEN=30) ::  variable_chr  !< dummy variable to read string
     541
     542
     543    READ ( 13 )  variable_chr
     544    DO  WHILE ( TRIM( variable_chr ) /= '*** end wtm ***' )
     545
     546       SELECT CASE ( TRIM( variable_chr ) )
     547
     548          CASE ( 'omega_gen' )
     549             READ ( 13 )  omega_gen
     550          CASE ( 'omega_gen_f' )
     551             READ ( 13 )  omega_gen_f
     552          CASE ( 'omega_gen_old' )
     553             READ ( 13 )  omega_gen_old
     554          CASE ( 'omega_gen_f_old' )
     555             READ ( 13 )  omega_gen_f_old
     556          CASE ( 'omega_rot' )
     557             READ ( 13 )  omega_rot
     558          CASE ( 'phi_yaw' )
     559             READ ( 13 )  phi_yaw
     560          CASE ( 'pitch_add' )
     561             READ ( 13 )  pitch_add
     562          CASE ( 'pitch_add_old' )
     563             READ ( 13 )  pitch_add_old
     564          CASE ( 'torque_gen' )
     565             READ ( 13 )  torque_gen
     566          CASE ( 'torque_gen_old' )
     567             READ ( 13 )  torque_gen_old
     568
     569       END SELECT
     570
     571       READ ( 13 )  variable_chr
     572
     573    ENDDO
     574
     575 END SUBROUTINE wtm_read_restart_data
     576
     577
     578!------------------------------------------------------------------------------!
     579! Description:
     580! ------------
     581!> Check namelist parameter
     582!------------------------------------------------------------------------------!
    474583    SUBROUTINE wtm_check_parameters
    475584
     
    594703
    595704!
    596 !--    Allocation of the 1D arrays for speed pitch_control
    597        ALLOCATE( omega_gen(1:nturbines) )
    598        ALLOCATE( omega_gen_old(1:nturbines) )
    599        ALLOCATE( omega_gen_f(1:nturbines) )
    600        ALLOCATE( omega_gen_f_old(1:nturbines) )
    601        ALLOCATE( pitch_add_old(1:nturbines) )
    602        ALLOCATE( torque_gen(1:nturbines) )
    603        ALLOCATE( torque_gen_old(1:nturbines) )
    604 
    605 !
    606705!--    Allocation of the 1D arrays for yaw control
    607706       ALLOCATE( yawdir(1:nturbines) )
     
    672771       thrust_rotor(:)          = 0.0_wp
    673772
    674        omega_gen(:)             = 0.0_wp
    675        omega_gen_old(:)         = 0.0_wp
    676        omega_gen_f(:)           = 0.0_wp
    677        omega_gen_f_old(:)       = 0.0_wp
    678        pitch_add_old(:)         = 0.0_wp
    679        torque_gen(:)            = 0.0_wp
    680        torque_gen_old(:)        = 0.0_wp
    681        
     773       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     774          omega_gen(:)             = 0.0_wp
     775          omega_gen_old(:)         = 0.0_wp
     776          omega_gen_f(:)           = 0.0_wp
     777          omega_gen_f_old(:)       = 0.0_wp
     778          pitch_add_old(:)         = 0.0_wp
     779          torque_gen(:)            = 0.0_wp
     780          torque_gen_old(:)        = 0.0_wp
     781       ENDIF
     782
    682783       yawdir(:)                = 0.0_wp
    683784       wdir(:)                  = 0.0_wp
     
    776877          CALL wtm_speed_control
    777878
     879          IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     880
     881             DO inot = 1, nturbines
     882
     883                IF ( nxl > i_hub(inot) ) THEN
     884                   torque_gen(inot) = 0.0_wp
     885                   omega_gen_f(inot) = 0.0_wp
     886                   omega_rot_l(inot) = 0.0_wp
     887                ENDIF
     888
     889                IF ( nxr < i_hub(inot) ) THEN
     890                   torque_gen(inot) = 0.0_wp
     891                   omega_gen_f(inot) = 0.0_wp
     892                   omega_rot_l(inot) = 0.0_wp
     893                ENDIF
     894
     895                IF ( nys > j_hub(inot) ) THEN
     896                   torque_gen(inot) = 0.0_wp
     897                   omega_gen_f(inot) = 0.0_wp
     898                   omega_rot_l(inot) = 0.0_wp
     899                ENDIF
     900
     901                IF ( nyn < j_hub(inot) ) THEN
     902                   torque_gen(inot) = 0.0_wp
     903                   omega_gen_f(inot) = 0.0_wp
     904                   omega_rot_l(inot) = 0.0_wp
     905                ENDIF
     906
     907                IF ( ( nxl <= i_hub(inot) ) .AND. ( nxr >= i_hub(inot) ) ) THEN
     908                   IF ( ( nys <= j_hub(inot) ) .AND. ( nyn >= j_hub(inot) ) ) THEN
     909
     910                      omega_rot_l(inot) = omega_gen(inot) / gear_ratio
     911
     912                   ENDIF
     913                ENDIF
     914
     915             END DO
     916
     917          ENDIF
     918
    778919       ENDIF
    779920
     
    814955!
    815956!--    Change yaw angle to rad:
    816        phi_yaw(:) = phi_yaw(:) * pi / 180.0_wp
     957       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     958          phi_yaw(:) = phi_yaw(:) * pi / 180.0_wp
     959       ENDIF
    817960
    818961
     
    23662509!--    At the first timestep the torque is set to its maximum to prevent
    23672510!--    an overspeeding of the rotor
    2368        torque_gen_old(:) = max_torque_gen 
     2511       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     2512          torque_gen_old(:) = max_torque_gen
     2513       ENDIF 
    23692514     
    23702515    END SUBROUTINE wtm_init_speed_control
Note: See TracChangeset for help on using the changeset viewer.