source: palm/trunk/SOURCE/wind_turbine_model_mod.f90 @ 3174

Last change on this file since 3174 was 3174, checked in by Giersch, 6 years ago

Bugfix in reading NAMELIST user_parameters, bugfix in wind turbine model related to the check of vertical stretching

  • Property svn:keywords set to Id
File size: 120.8 KB
RevLine 
[1820]1!> @file wind_turbine_model_mod.f90
[1912]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1819]4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1819]9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[2718]17! Copyright 2009-2018 Carl von Ossietzky Universitaet Oldenburg
18! Copyright 1997-2018 Leibniz Universitaet Hannover
[1912]19!------------------------------------------------------------------------------!
[1819]20!
21! Current revisions:
22! -----------------
[1913]23!
[3139]24!
[1913]25! Former revisions:
26! -----------------
27! $Id: wind_turbine_model_mod.f90 3174 2018-07-26 13:46:50Z Giersch $
[3174]28! Check for vertical stretching has been revised.
29!
30! 3139 2018-07-17 11:30:10Z Giersch
[3139]31! Bugfix in calculation of alpha_attack
32!
33! 3069 2018-06-15 07:56:09Z witha
[3069]34! Initialization of some arrays added
35!
36! 3066 2018-06-12 08:55:55Z Giersch
[3066]37! Error message revised
[3069]38!
[3066]39! 3065 2018-06-12 07:03:02Z Giersch
[3065]40! dz was replaced by dz(1), error message concerning grid stretching has been
41! introduced
42!
43! 3049 2018-05-29 13:52:36Z Giersch
[3049]44! Error messages revised
45!
46! 2932 2018-03-26 09:39:22Z Giersch
[2932]47! renamed wind_turbine_par to wind_turbine_parameters
48!
49! 2894 2018-03-15 09:17:58Z Giersch
[2894]50! variable named found has been introduced for checking if restart data was
51! found, reading of restart strings has been moved completely to
52! read_restart_data_mod, wind_turbine_prerun flag has been removed, redundant
53! skipping function has been removed, wtm_read/write_restart_data have been
54! renamed to wtm_r/wrd_global, wtm_rrd_global is called in
55! read_restart_data_mod now, marker *** end wtm *** was removed, strings and
56! their respective lengths are written out and read now in case of restart
57! runs to get rid of prescribed character lengths, CASE DEFAULT was added if
58! restart data is read
59!
60! 2885 2018-03-14 11:02:46Z Giersch
[2836]61! Bugfix in interpolation of lift and drag coefficients on fine grid of radius
62! segments and angles of attack, speed-up of the initialization of the wind
63! turbine model
64!
65! 2792 2018-02-07 06:45:29Z Giersch
[2792]66! omega_rot_l has to be calculated after determining the indices for the hub in
67! case of restart runs
68!
69! 2776 2018-01-31 10:44:42Z Giersch
[2776]70! wind_turbine_prerun flag is used to define if module
71! related parameters were outputted as restart data
72!
73! 2718 2018-01-02 08:49:38Z maronga
[2716]74! Corrected "Former revisions" section
75!
76! 2696 2017-12-14 17:12:51Z kanani
77! Change in file header (GPL part)
78!
79! 2669 2017-12-06 16:03:27Z raasch
[2669]80! filename of turbine output changed to WTM_OUTPUT_DATA. File extension now
81! includes the nest domain number. Turbine extension changed to "_T##"
82!
83! 2576 2017-10-24 13:49:46Z Giersch
[2894]84! Definition of a new function called wtm_skip_global to skip module
[2576]85! parameters during reading restart data
86!
87! 2563 2017-10-19 15:36:10Z Giersch
[2563]88! Restart runs with wind turbine model are possible now. For this purpose, two
89! new subroutines wtm_write_restart_data and wtm_read_restart_data had to be
90! defined
91!
92! 2553 2017-10-18 08:03:45Z Giersch
[2553]93! Bugfix of vertical loop in wtm_tendencies to account for different turbine
94! heights, bugfix of the interpolation of the u-component concerning the
95! vertical index and further small adjustments of the programming style
96!
97! 2410 2017-09-06 08:16:30Z Giersch
[2410]98! Revise error message PA0462
99!
100! 2349 2017-08-10 15:44:04Z Giersch
[2349]101! Add parameter pitch_rate to namelist and revise/add error messages
102!
103! 2343 2017-08-08 11:28:43Z Giersch
[2341]104! Unit correction in Doxygen comments
[2323]105!
[2343]106! 2323 2017-07-26 12:57:38Z Giersch
107! Change unit number of file WTM_DATA from 201 to 90
108
[2323]109! 2322 2017-07-26 08:30:28Z Giersch
[2322]110! Bugfix of error message and assign error numbers
111!
112! 2257 2017-06-07 14:07:05Z witha
[2257]113! Bugfix: turb_cl_tab and turb_cd_tab were set to zero before being allocated
[1844]114!
[2257]115! 2233 2017-05-30 18:08:54Z suehring
116!
[2233]117! 2232 2017-05-30 17:47:52Z suehring
118! Adjustments to new topography concept
119!
[2153]120! 2152 2017-02-17 13:27:24Z lvollmer
121! Bugfix in subroutine wtm_read_blade_tables
122! Addition of a tip loss model
123!
[2016]124! 2015 2016-09-28 08:45:18Z lvollmer
125! Bugfix of pitch control
126!
[2001]127! 2000 2016-08-20 18:09:15Z knoop
128! Forced header and separation lines into 80 columns
129!
[1930]130! 1929 2016-06-09 16:25:25Z suehring
131! Bugfix: added preprocessor directives for parallel and serial mode
132!
[1917]133! 1914 2016-05-26 14:44:07Z witha
[1821]134! Initial revision
135!
[1819]136!
137! Description:
138! ------------
139!> This module calculates the effect of wind turbines on the flow fields. The
140!> initial version contains only the advanced actuator disk with rotation method
141!> (ADM-R).
142!> The wind turbines include the tower effect, can be yawed and tilted.
143!> The wind turbine model includes controllers for rotational speed, pitch and
144!> yaw.
145!> Currently some specifications of the NREL 5 MW reference turbine
146!> are hardcoded whereas most input data comes from separate files (currently
147!> external, planned to be included as namelist which will be read in
148!> automatically).
149!>
[3065]150!> @todo Replace dz(1) appropriatly to account for grid stretching
[1819]151!> @todo Revise code according to PALM Coding Standard
152!> @todo Implement ADM and ALM turbine models
153!> @todo Generate header information
[1917]154!> @todo Implement further parameter checks and error messages
[1819]155!> @todo Revise and add code documentation
156!> @todo Output turbine parameters as timeseries
157!> @todo Include additional output variables
[1864]158!> @todo Revise smearing the forces for turbines in yaw
159!> @todo Revise nacelle and tower parameterization
160!> @todo Allow different turbine types in one simulation
[1819]161!
162!------------------------------------------------------------------------------!
163 MODULE wind_turbine_model_mod
164
165    USE arrays_3d,                                                             &
[2553]166        ONLY:  tend, u, v, w, zu, zw
[1819]167
[2553]168    USE constants,                                                             &
169        ONLY:  pi
[1819]170
171    USE control_parameters,                                                    &
[2669]172        ONLY:  coupling_char, dt_3d, dz, message_string, simulated_time,       &
[2894]173               wind_turbine, initializing_actions
[1819]174
175    USE cpulog,                                                                &
176        ONLY:  cpu_log, log_point_s
177
178    USE grid_variables,                                                        &
179        ONLY:  ddx, dx, ddy, dy
180
181    USE indices,                                                               &
182        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
[2232]183               nzb, nzt, wall_flags_0
[1819]184
185    USE kinds
186
187    USE pegrid
188
189
190    IMPLICIT NONE
191
[1864]192    PRIVATE
[1819]193
194!
195!-- Variables specified in the namelist wind_turbine_par
196
[1864]197    INTEGER(iwp) ::  nairfoils = 8   !< number of airfoils of the used turbine model (for ADM-R and ALM)
[1839]198    INTEGER(iwp) ::  nturbines = 1   !< number of turbines
[1819]199
[1839]200    LOGICAL ::  pitch_control = .FALSE.   !< switch for use of pitch controller
201    LOGICAL ::  speed_control = .FALSE.   !< switch for use of speed controller
202    LOGICAL ::  yaw_control   = .FALSE.   !< switch for use of yaw controller
[2152]203    LOGICAL ::  tl_cor        = .FALSE.    !< switch for use of tip loss correct.
[1819]204
[1839]205    REAL(wp) ::  segment_length  = 1.0_wp          !< length of the segments, the rotor area is divided into
206                                                   !< (in tangential direction, as factor of MIN(dx,dy,dz))
207    REAL(wp) ::  segment_width   = 0.5_wp          !< width of the segments, the rotor area is divided into
208                                                   !< (in radial direction, as factor of MIN(dx,dy,dz))
209    REAL(wp) ::  time_turbine_on = 0.0_wp          !< time at which turbines are started
210    REAL(wp) ::  tilt            = 0.0_wp          !< vertical tilt of the rotor [degree] ( positive = backwards )
[1819]211
[1912]212    REAL(wp), DIMENSION(1:100) ::  dtow             = 0.0_wp  !< tower diameter [m]
[2553]213    REAL(wp), DIMENSION(1:100) ::  omega_rot        = 0.9_wp  !< inital or constant rotor speed [rad/s]
[1912]214    REAL(wp), DIMENSION(1:100) ::  phi_yaw          = 0.0_wp  !< yaw angle [degree] ( clockwise, 0 = facing west )
215    REAL(wp), DIMENSION(1:100) ::  pitch_add        = 0.0_wp  !< constant pitch angle
216    REAL(wp), DIMENSION(1:100) ::  rcx        = 9999999.9_wp  !< position of hub in x-direction
217    REAL(wp), DIMENSION(1:100) ::  rcy        = 9999999.9_wp  !< position of hub in y-direction
218    REAL(wp), DIMENSION(1:100) ::  rcz        = 9999999.9_wp  !< position of hub in z-direction
219    REAL(wp), DIMENSION(1:100) ::  rnac             = 0.0_wp  !< nacelle diameter [m]
220    REAL(wp), DIMENSION(1:100) ::  rr              = 63.0_wp  !< rotor radius [m]
221    REAL(wp), DIMENSION(1:100) ::  turb_cd_nacelle = 0.85_wp  !< drag coefficient for nacelle
222    REAL(wp), DIMENSION(1:100) ::  turb_cd_tower    = 1.2_wp  !< drag coefficient for tower
[1839]223
[1819]224!
225!-- Variables specified in the namelist for speed controller
226!-- Default values are from the NREL 5MW research turbine (Jonkman, 2008)
227
[1912]228    REAL(wp) ::  rated_power    = 5296610.0_wp    !< rated turbine power [W]
[1839]229    REAL(wp) ::  gear_ratio     = 97.0_wp         !< Gear ratio from rotor to generator
[2341]230    REAL(wp) ::  inertia_rot    = 34784179.0_wp   !< Inertia of the rotor [kg*m2]
231    REAL(wp) ::  inertia_gen    = 534.116_wp      !< Inertia of the generator [kg*m2]
[1839]232    REAL(wp) ::  gen_eff        = 0.944_wp        !< Electric efficiency of the generator
233    REAL(wp) ::  gear_eff       = 1.0_wp          !< Loss between rotor and generator
234    REAL(wp) ::  air_dens       = 1.225_wp        !< Air density to convert to W [kg/m3]
235    REAL(wp) ::  rated_genspeed = 121.6805_wp     !< Rated generator speed [rad/s]
[1912]236    REAL(wp) ::  max_torque_gen = 47402.91_wp     !< Maximum of the generator torque [Nm]
[1839]237    REAL(wp) ::  slope2         = 2.332287_wp     !< Slope constant for region 2
238    REAL(wp) ::  min_reg2       = 91.21091_wp     !< Lower generator speed boundary of region 2 [rad/s]
239    REAL(wp) ::  min_reg15      = 70.16224_wp     !< Lower generator speed boundary of region 1.5 [rad/s]
[1912]240    REAL(wp) ::  max_trq_rate   = 15000.0_wp      !< Max generator torque increase [Nm/s]
241    REAL(wp) ::  pitch_rate     = 8.0_wp          !< Max pitch rate [degree/s]
[1839]242
[1912]243
[1819]244!
245!-- Variables specified in the namelist for yaw control
246
[1839]247    REAL(wp) ::  yaw_speed = 0.005236_wp   !< speed of the yaw actuator [rad/s]
248    REAL(wp) ::  max_miss = 0.08726_wp     !< maximum tolerated yaw missalignment [rad]
249    REAL(wp) ::  min_miss = 0.008726_wp    !< minimum yaw missalignment for which the actuator stops [rad]
250
[1819]251!
252!-- Set flag for output files TURBINE_PARAMETERS
253    TYPE file_status
254       LOGICAL ::  opened, opened_before
255    END TYPE file_status
256   
[1912]257    TYPE(file_status), DIMENSION(500) :: openfile_turb_mod =                   &
258                                         file_status(.FALSE.,.FALSE.)
[1819]259
260!
261!-- Variables for initialization of the turbine model
262
[1839]263    INTEGER(iwp) ::  inot         !< turbine loop index (turbine id)
264    INTEGER(iwp) ::  nsegs_max    !< maximum number of segments (all turbines, required for allocation of arrays)
265    INTEGER(iwp) ::  nrings_max   !< maximum number of rings (all turbines, required for allocation of arrays)
266    INTEGER(iwp) ::  ring         !< ring loop index (ring number)
267    INTEGER(iwp) ::  rr_int       !<
268    INTEGER(iwp) ::  upper_end    !<
[1819]269
[1839]270    INTEGER(iwp), DIMENSION(1) ::  lct   !<
[1819]271
[1912]272    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i_hub     !< index belonging to x-position of the turbine
273    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i_smear   !< index defining the area for the smearing of the forces (x-direction)
274    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j_hub     !< index belonging to y-position of the turbine
275    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j_smear   !< index defining the area for the smearing of the forces (y-direction)
276    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_hub     !< index belonging to hub height
277    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_smear   !< index defining the area for the smearing of the forces (z-direction)
278    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nrings    !< number of rings per turbine
279    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nsegs_total !< total number of segments per turbine
[1819]280
[1912]281    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nsegs   !< number of segments per ring and turbine
[1819]282
[1912]283!
284!-  parameters for the smearing from the rotor to the cartesian grid   
[1864]285    REAL(wp) ::  pol_a            !< parameter for the polynomial smearing fct
286    REAL(wp) ::  pol_b            !< parameter for the polynomial smearing fct
[1912]287    REAL(wp) ::  delta_t_factor   !<
[1864]288    REAL(wp) ::  eps_factor       !< 
[1839]289    REAL(wp) ::  eps_min          !<
290    REAL(wp) ::  eps_min2         !<
291    REAL(wp) ::  sqrt_arg         !<
[1819]292
[1839]293!
294!-- Variables for the calculation of lift and drag coefficients
[1912]295    REAL(wp), DIMENSION(:), ALLOCATABLE  ::  ard     !<
296    REAL(wp), DIMENSION(:), ALLOCATABLE  ::  crd     !<
297    REAL(wp), DIMENSION(:), ALLOCATABLE  ::  delta_r !< radial segment length
298    REAL(wp), DIMENSION(:), ALLOCATABLE  ::  lrd     !<
[1864]299   
[1912]300    REAL(wp) ::  accu_cl_cd_tab = 0.1_wp  !< Accuracy of the interpolation of
301                                          !< the lift and drag coeff [deg]
[1819]302
[1912]303    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: turb_cd_tab   !< table of the blade drag coefficient
304    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: turb_cl_tab   !< table of the blade lift coefficient
[1819]305
[1912]306    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  nac_cd_surf  !< 3d field of the tower drag coefficient
307    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tow_cd_surf  !< 3d field of the nacelle drag coefficient
[1819]308
309!
310!-- Variables for the calculation of the forces
[1912]311     
[1839]312    REAL(wp) ::  cur_r                       !<
313    REAL(wp) ::  phi_rotor                   !<
314    REAL(wp) ::  pre_factor                  !< 
315    REAL(wp) ::  torque_seg                  !<
316    REAL(wp) ::  u_int_l                     !<
317    REAL(wp) ::  u_int_u                     !<
318    REAL(wp) ::  u_rot                       !<
319    REAL(wp) ::  v_int_l                     !<
320    REAL(wp) ::  v_int_u                     !<
321    REAL(wp) ::  w_int_l                     !<
322    REAL(wp) ::  w_int_u                     !<
[1912]323!
324!-  Tendencies from the nacelle and tower thrust
325    REAL(wp) ::  tend_nac_x = 0.0_wp  !<
326    REAL(wp) ::  tend_tow_x = 0.0_wp  !<
327    REAL(wp) ::  tend_nac_y = 0.0_wp  !<
328    REAL(wp) ::  tend_tow_y = 0.0_wp  !<
[1819]329
[1912]330    REAL(wp), DIMENSION(:), ALLOCATABLE ::  alpha_attack !<
331    REAL(wp), DIMENSION(:), ALLOCATABLE ::  chord        !<
332    REAL(wp), DIMENSION(:), ALLOCATABLE ::  phi_rel      !<
333    REAL(wp), DIMENSION(:), ALLOCATABLE ::  torque_total !<
334    REAL(wp), DIMENSION(:), ALLOCATABLE ::  thrust_rotor !<
335    REAL(wp), DIMENSION(:), ALLOCATABLE ::  turb_cl      !<
336    REAL(wp), DIMENSION(:), ALLOCATABLE ::  turb_cd      !<
337    REAL(wp), DIMENSION(:), ALLOCATABLE ::  vrel         !<
338    REAL(wp), DIMENSION(:), ALLOCATABLE ::  vtheta       !<
339
340    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rbx, rby, rbz     !< coordinates of the blade elements
341    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rotx, roty, rotz  !< normal vectors to the rotor coordinates
342
343!
344!-  Fields for the interpolation of velocities on the rotor grid
345    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_int       !<
346    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_int_1_l   !<
347    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_int       !<
348    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_int_1_l   !<
349    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_int       !<
350    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_int_1_l   !<
351   
352!
353!-  rotor tendencies on the segments
354    REAL(wp), DIMENSION(:), ALLOCATABLE :: thrust_seg   !<
355    REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_seg_y !<
356    REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_seg_z !<   
357
358!
359!-  rotor tendencies on the rings
360    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  thrust_ring       !<
361    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  torque_ring_y     !<
362    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  torque_ring_z     !<
363   
364!
365!-  rotor tendencies on rotor grids for all turbines
366    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  thrust      !<
367    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  torque_y    !<
368    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  torque_z    !<
369
370!
371!-  rotor tendencies on coordinate grid
372    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rot_tend_x  !<
373    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rot_tend_y  !<
374    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rot_tend_z  !<
375!   
376!-  variables for the rotation of the rotor coordinates       
377    REAL(wp), DIMENSION(1:100,1:3,1:3) ::  rot_coord_trans  !< matrix for rotation of rotor coordinates
378   
[1839]379    REAL(wp), DIMENSION(1:3) ::  rot_eigen_rad   !<
380    REAL(wp), DIMENSION(1:3) ::  rot_eigen_azi   !<
381    REAL(wp), DIMENSION(1:3) ::  rot_eigen_nor   !<
382    REAL(wp), DIMENSION(1:3) ::  re              !<
383    REAL(wp), DIMENSION(1:3) ::  rea             !<
384    REAL(wp), DIMENSION(1:3) ::  ren             !<
385    REAL(wp), DIMENSION(1:3) ::  rote            !<
386    REAL(wp), DIMENSION(1:3) ::  rota            !<
387    REAL(wp), DIMENSION(1:3) ::  rotn            !<
[1819]388
[1839]389!
390!-- Fixed variables for the speed controller
[1819]391
[1912]392    LOGICAL  ::  start_up = .TRUE.   !<
[1864]393   
[1912]394    REAL(wp) ::  Fcorner             !< corner freq for the controller low pass filter
395    REAL(wp) ::  min_reg25           !< min region 2.5
396    REAL(wp) ::  om_rate             !< rotor speed change
397    REAL(wp) ::  slope15             !< slope in region 1.5
398    REAL(wp) ::  slope25             !< slope in region 2.5
399    REAL(wp) ::  trq_rate            !< torque change
400    REAL(wp) ::  vs_sysp             !<
401    REAL(wp) ::  lp_coeff            !< coeff for the controller low pass filter
[1819]402
[1864]403    REAL(wp), DIMENSION(100) :: omega_rot_l = 0.0_wp !< local rot speed [rad/s]
[2563]404
[1839]405!
406!-- Fixed variables for the yaw controller
[1819]407
[1912]408    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  yawdir           !< direction to yaw
409    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  phi_yaw_l        !< local (cpu) yaw angle
410    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  wd30_l           !< local (cpu) long running avg of the wd
411    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  wd2_l            !< local (cpu) short running avg of the wd
412    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  wdir             !< wind direction at hub
413    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  u_inflow         !< wind speed at hub
414    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  wdir_l           !<
415    REAL(wp), DIMENSION(:)  , ALLOCATABLE ::  u_inflow_l       !<
416    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  wd30             !<
417    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  wd2              !<
418    LOGICAL,  DIMENSION(1:100)            ::  doyaw = .FALSE.  !<
419    INTEGER(iwp)                          ::  WDLON            !<
420    INTEGER(iwp)                          ::  WDSHO            !<
[1819]421
[2563]422!
423!-- Variables that have to be saved in the binary file for restarts
424    REAL(wp), DIMENSION(1:100) ::  pitch_add_old           = 0.0_wp  !< old constant pitch angle
425    REAL(wp), DIMENSION(1:100) ::  omega_gen               = 0.0_wp  !< curr. generator speed
426    REAL(wp), DIMENSION(1:100) ::  omega_gen_f             = 0.0_wp  !< filtered generator speed
427    REAL(wp), DIMENSION(1:100) ::  omega_gen_old           = 0.0_wp  !< last generator speed
428    REAL(wp), DIMENSION(1:100) ::  omega_gen_f_old         = 0.0_wp  !< last filtered generator speed
429    REAL(wp), DIMENSION(1:100) ::  torque_gen              = 0.0_wp  !< generator torque
430    REAL(wp), DIMENSION(1:100) ::  torque_gen_old          = 0.0_wp  !< last generator torque
[1819]431
[2563]432
[1839]433    SAVE
[1819]434
[1839]435
436    INTERFACE wtm_parin
437       MODULE PROCEDURE wtm_parin
438    END INTERFACE wtm_parin
[2563]439
[2894]440    INTERFACE wtm_wrd_global 
441       MODULE PROCEDURE wtm_wrd_global 
442    END INTERFACE wtm_wrd_global
[2576]443
[2894]444    INTERFACE wtm_rrd_global 
445       MODULE PROCEDURE wtm_rrd_global
446    END INTERFACE wtm_rrd_global 
[1912]447   
448    INTERFACE wtm_check_parameters
449       MODULE PROCEDURE wtm_check_parameters
450    END INTERFACE wtm_check_parameters
[1839]451       
452    INTERFACE wtm_init_arrays
453       MODULE PROCEDURE wtm_init_arrays
454    END INTERFACE wtm_init_arrays
455
456    INTERFACE wtm_init
457       MODULE PROCEDURE wtm_init
458    END INTERFACE wtm_init
459   
[1912]460    INTERFACE wtm_read_blade_tables
461       MODULE PROCEDURE wtm_read_blade_tables
462    END INTERFACE wtm_read_blade_tables
[1839]463           
[1819]464    INTERFACE wtm_forces
465       MODULE PROCEDURE wtm_forces
[2553]466    END INTERFACE wtm_forces
467
468    INTERFACE wtm_yawcontrol
[1839]469       MODULE PROCEDURE wtm_yawcontrol
[2553]470    END INTERFACE wtm_yawcontrol
[1864]471   
472    INTERFACE wtm_rotate_rotor
473       MODULE PROCEDURE wtm_rotate_rotor
474    END INTERFACE wtm_rotate_rotor
475   
476    INTERFACE wtm_speed_control
477       MODULE PROCEDURE wtm_init_speed_control
478       MODULE PROCEDURE wtm_speed_control
479    END INTERFACE wtm_speed_control
[1819]480
481    INTERFACE wtm_tendencies
482       MODULE PROCEDURE wtm_tendencies
483       MODULE PROCEDURE wtm_tendencies_ij
484    END INTERFACE wtm_tendencies
[1864]485   
486   
[1912]487    PUBLIC wtm_check_parameters, wtm_forces, wtm_init, wtm_init_arrays,        &
[2894]488           wtm_parin, wtm_wrd_global, wtm_rrd_global, wtm_tendencies
[1819]489
[2563]490
[1819]491 CONTAINS
492
493
494!------------------------------------------------------------------------------!
495! Description:
496! ------------
[1839]497!> Parin for &wind_turbine_par for wind turbine model
[1819]498!------------------------------------------------------------------------------!
[1839]499    SUBROUTINE wtm_parin
[1819]500
501
502       IMPLICIT NONE
[1912]503       
504       INTEGER(iwp) ::  ierrn       !<
[1819]505
[1839]506       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
507
508       NAMELIST /wind_turbine_par/   air_dens, dtow, gear_eff, gear_ratio,     &
[1864]509                                  gen_eff, inertia_gen, inertia_rot, max_miss, &
[1839]510                                  max_torque_gen, max_trq_rate, min_miss,      &
[1864]511                                  min_reg15, min_reg2, nairfoils, nturbines,   &
[1912]512                                  omega_rot, phi_yaw, pitch_add, pitch_control,&
[1839]513                                  rated_genspeed, rated_power, rcx, rcy, rcz,  &
514                                  rnac, rr, segment_length, segment_width,     &
[1864]515                                  slope2, speed_control, tilt, time_turbine_on,&
[2349]516                                  turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
[2152]517                                  yaw_control, yaw_speed, tl_cor
[2932]518                                 
519       NAMELIST /wind_turbine_parameters/                                      &
520                                  air_dens, dtow, gear_eff, gear_ratio,        &
521                                  gen_eff, inertia_gen, inertia_rot, max_miss, &
522                                  max_torque_gen, max_trq_rate, min_miss,      &
523                                  min_reg15, min_reg2, nairfoils, nturbines,   &
524                                  omega_rot, phi_yaw, pitch_add, pitch_control,&
525                                  rated_genspeed, rated_power, rcx, rcy, rcz,  &
526                                  rnac, rr, segment_length, segment_width,     &
527                                  slope2, speed_control, tilt, time_turbine_on,&
528                                  turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
529                                  yaw_control, yaw_speed, tl_cor
[1819]530!
[1839]531!--    Try to find wind turbine model package
532       REWIND ( 11 )
533       line = ' '
[2932]534       DO  WHILE ( INDEX( line, '&wind_turbine_parameters' ) == 0 )
[1839]535          READ ( 11, '(A)', END=10 )  line
536       ENDDO
537       BACKSPACE ( 11 )
538
539!
540!--    Read user-defined namelist
[2932]541       READ ( 11, wind_turbine_parameters, IOSTAT=ierrn )
542
543       IF ( ierrn < 0 )  THEN
544          message_string = 'no wind_turbine_parameters-NAMELIST found: '  //    &
545                           'End of file has reached'
546          CALL message( 'wtm_parin', 'PA0460', 1, 2, 0, 6, 0 )
547       ELSEIF ( ierrn > 0 ) THEN
548          message_string = 'errors in wind_turbine_parameters-NAMELIST: '  //   &
549                           'some variables for steering may not be properly set'
550          CALL message( 'wtm_parin', 'PA0466', 1, 2, 0, 6, 0 )               
551       ENDIF
552       
553!
554!--    Set flag that indicates that the wind turbine model is switched on
555       wind_turbine = .TRUE.
556       
557       GOTO 12
558
559!
560!--    Try to find wind turbine model package
561 10    REWIND ( 11 )
562       line = ' '
563       DO  WHILE ( INDEX( line, '&wind_turbine_par' ) == 0 )
564          READ ( 11, '(A)', END=12 )  line
565       ENDDO
566       BACKSPACE ( 11 )
567
568!
569!--    Read user-defined namelist
[1912]570       READ ( 11, wind_turbine_par, IOSTAT=ierrn )
[2349]571
[1912]572       IF ( ierrn < 0 )  THEN
[2349]573          message_string = 'no wind_turbine_par-NAMELIST found: '  //          &
574                           'End of file has reached'
[2322]575          CALL message( 'wtm_parin', 'PA0460', 1, 2, 0, 6, 0 )
[2349]576       ELSEIF ( ierrn > 0 ) THEN
[2932]577          message_string = 'errors in wind_turbine_par-NAMELIST: '  //         &
[2349]578                           'some variables for steering may not be properly set'
579          CALL message( 'wtm_parin', 'PA0466', 1, 2, 0, 6, 0 )               
[1912]580       ENDIF
[2932]581     
582       message_string = 'namelist wind_tubrine_par is deprecated and will ' // &
[3046]583                        'be removed in near future. &Please use namelist ' //  &
[2932]584                        'wind_turbine_parameters instead' 
585       CALL message( 'wtm_parin', 'PA0487', 0, 1, 0, 6, 0 )     
586     
[1839]587!
588!--    Set flag that indicates that the wind turbine model is switched on
589       wind_turbine = .TRUE.
590
[2932]591 12    CONTINUE   ! TBD Change from continue, mit ierrn machen
[2563]592
[1839]593
594    END SUBROUTINE wtm_parin
595
[2563]596
597!------------------------------------------------------------------------------!
598! Description:
599! ------------
[2894]600!> This routine writes the respective restart data.
[2576]601!------------------------------------------------------------------------------!
[2894]602    SUBROUTINE wtm_wrd_global 
[2576]603
604
[2563]605       IMPLICIT NONE
[2776]606
[2563]607       
[2894]608       CALL wrd_write_string( 'omega_gen' )
[2563]609       WRITE ( 14 )  omega_gen
[2894]610
611       CALL wrd_write_string( 'omega_gen_f' )
[2563]612       WRITE ( 14 )  omega_gen_f
[2894]613
614       CALL wrd_write_string( 'omega_gen_f_old' )
[2563]615       WRITE ( 14 )  omega_gen_f_old
[2894]616
617       CALL wrd_write_string( 'omega_gen_old' )
[2563]618       WRITE ( 14 )  omega_gen_old
[2894]619
620       CALL wrd_write_string( 'omega_rot' )
[2563]621       WRITE ( 14 )  omega_rot
[2894]622
623       CALL wrd_write_string( 'phi_yaw' )
624       WRITE ( 14 )  phi_yaw
625
626       CALL wrd_write_string( 'pitch_add' )
[2563]627       WRITE ( 14 )  pitch_add
[2894]628
629       CALL wrd_write_string( 'pitch_add_old' )
[2563]630       WRITE ( 14 )  pitch_add_old
[2894]631
632       CALL wrd_write_string( 'torque_gen' )
[2563]633       WRITE ( 14 )  torque_gen
[2894]634
635       CALL wrd_write_string( 'torque_gen_old' )
[2563]636       WRITE ( 14 )  torque_gen_old
[2894]637
[2563]638       
[2894]639    END SUBROUTINE wtm_wrd_global   
[2563]640
641
642!------------------------------------------------------------------------------!
643! Description:
644! ------------
645!> This routine reads the respective restart data.
646!------------------------------------------------------------------------------!
[2894]647 SUBROUTINE wtm_rrd_global( found )
[2563]648
649
[2894]650    USE control_parameters,                                                    &
651        ONLY: length, restart_string
652
653
[2563]654    IMPLICIT NONE
655
[2894]656    LOGICAL, INTENT(OUT)  ::  found 
[2563]657
658
[2894]659    found = .TRUE.
[2563]660
661
[2894]662    SELECT CASE ( restart_string(1:length) )
[2563]663
[2894]664       CASE ( 'omega_gen' )
665          READ ( 13 )  omega_gen
666       CASE ( 'omega_gen_f' )
667          READ ( 13 )  omega_gen_f
668       CASE ( 'omega_gen_f_old' )
669          READ ( 13 )  omega_gen_f_old
670       CASE ( 'omega_gen_old' )
671          READ ( 13 )  omega_gen_old
672       CASE ( 'omega_rot' )
673          READ ( 13 )  omega_rot
674       CASE ( 'phi_yaw' )
675          READ ( 13 )  phi_yaw
676       CASE ( 'pitch_add' )
677          READ ( 13 )  pitch_add
678       CASE ( 'pitch_add_old' )
679          READ ( 13 )  pitch_add_old
680       CASE ( 'torque_gen' )
681          READ ( 13 )  torque_gen
682       CASE ( 'torque_gen_old' )
683          READ ( 13 )  torque_gen_old
[2563]684
[2894]685       CASE DEFAULT
[2563]686
[2894]687          found = .FALSE.
[2563]688
[2894]689    END SELECT
690   
[2563]691
[2894]692 END SUBROUTINE wtm_rrd_global
693
694
[2563]695!------------------------------------------------------------------------------!
696! Description:
697! ------------
698!> Check namelist parameter
699!------------------------------------------------------------------------------!
[1912]700    SUBROUTINE wtm_check_parameters
701
702   
703       IMPLICIT NONE
704   
705       IF ( ( .NOT.speed_control ) .AND. pitch_control )  THEN
706          message_string = 'pitch_control = .TRUE. requires '//                &
707                           'speed_control = .TRUE.'
[2322]708          CALL message( 'wtm_check_parameters', 'PA0461', 1, 2, 0, 6, 0 )
[1912]709       ENDIF
710       
[2322]711       IF ( ANY( omega_rot(1:nturbines) < 0.0 ) )  THEN
712          message_string = 'omega_rot < 0.0, Please set omega_rot to '     // &
[2792]713                           'a value equal or larger than zero'
[2322]714          CALL message( 'wtm_check_parameters', 'PA0462', 1, 2, 0, 6, 0 )
[1912]715       ENDIF
716       
717       
718       IF ( ANY( rcx(1:nturbines) == 9999999.9_wp ) .OR.                       &
719            ANY( rcy(1:nturbines) == 9999999.9_wp ) .OR.                       &
720            ANY( rcz(1:nturbines) == 9999999.9_wp ) )  THEN
721         
722          message_string = 'rcx, rcy, rcz '                                 // &
723                           'have to be given for each turbine.'         
[2322]724          CALL message( 'wtm_check_parameters', 'PA0463', 1, 2, 0, 6, 0 )         
[1912]725         
726       ENDIF
727
728 
729    END SUBROUTINE wtm_check_parameters 
730   
731                                       
[1839]732!------------------------------------------------------------------------------!
733! Description:
734! ------------
735!> Allocate wind turbine model arrays
736!------------------------------------------------------------------------------!
737    SUBROUTINE wtm_init_arrays
738
739
740       IMPLICIT NONE
741
[1864]742       REAL(wp) ::  delta_r_factor   !<
743       REAL(wp) ::  delta_r_init     !<
744
[1839]745!
746!--    To be able to allocate arrays with dimension of rotor rings and segments,
[1819]747!--    the maximum possible numbers of rings and segments have to be calculated:
748
749       ALLOCATE( nrings(1:nturbines) )
750       ALLOCATE( delta_r(1:nturbines) )
751
752       nrings(:)  = 0
753       delta_r(:) = 0.0_wp
754
755!
756!--    Thickness (radial) of each ring and length (tangential) of each segment:
757       delta_r_factor = segment_width
758       delta_t_factor = segment_length
[3065]759       delta_r_init   = delta_r_factor * MIN( dx, dy, dz(1))
[1819]760
761       DO inot = 1, nturbines
762!
763!--       Determine number of rings:
764          nrings(inot) = NINT( rr(inot) / delta_r_init )
765
766          delta_r(inot) = rr(inot) / nrings(inot)
767
768       ENDDO
769
770       nrings_max = MAXVAL(nrings)
771
772       ALLOCATE( nsegs(1:nrings_max,1:nturbines) )
773       ALLOCATE( nsegs_total(1:nturbines) )
774
775       nsegs(:,:)     = 0
776       nsegs_total(:) = 0
777
778
779       DO inot = 1, nturbines
780          DO ring = 1, nrings(inot)
781!
782!--          Determine number of segments for each ring:
[1839]783             nsegs(ring,inot) = MAX( 8, CEILING( delta_r_factor * pi *         &
784                                                 ( 2.0_wp * ring - 1.0_wp ) /  &
785                                                 delta_t_factor ) )
[1819]786          ENDDO
787!
788!--       Total sum of all rotor segments:
[1839]789          nsegs_total(inot) = SUM( nsegs(:,inot) )
[1819]790
791       ENDDO
792
793!
794!--    Maximum number of segments per ring:
795       nsegs_max = MAXVAL(nsegs)
796
[1864]797!!
798!!--    TODO: Folgendes im Header ausgeben!
799!       IF ( myid == 0 )  THEN
800!          PRINT*, 'nrings(1) = ', nrings(1)
801!          PRINT*, '--------------------------------------------------'
802!          PRINT*, 'nsegs(:,1) = ', nsegs(:,1)
803!          PRINT*, '--------------------------------------------------'
804!          PRINT*, 'nrings_max = ', nrings_max
805!          PRINT*, 'nsegs_max = ', nsegs_max
806!          PRINT*, 'nsegs_total(1) = ', nsegs_total(1)
807!       ENDIF
[1819]808
809
810!
811!--    Allocate 1D arrays (dimension = number of turbines)
812       ALLOCATE( i_hub(1:nturbines) )
813       ALLOCATE( i_smear(1:nturbines) )
814       ALLOCATE( j_hub(1:nturbines) )
815       ALLOCATE( j_smear(1:nturbines) )
816       ALLOCATE( k_hub(1:nturbines) )
817       ALLOCATE( k_smear(1:nturbines) )
818       ALLOCATE( torque_total(1:nturbines) )
[1912]819       ALLOCATE( thrust_rotor(1:nturbines) )
[1819]820
821!
822!--    Allocation of the 1D arrays for yaw control
823       ALLOCATE( yawdir(1:nturbines) )
824       ALLOCATE( u_inflow(1:nturbines) )
825       ALLOCATE( wdir(1:nturbines) )
826       ALLOCATE( u_inflow_l(1:nturbines) )
827       ALLOCATE( wdir_l(1:nturbines) )
828       ALLOCATE( phi_yaw_l(1:nturbines) )
829       
830!
831!--    Allocate 1D arrays (dimension = number of rotor segments)
832       ALLOCATE( alpha_attack(1:nsegs_max) )
833       ALLOCATE( chord(1:nsegs_max) )
834       ALLOCATE( phi_rel(1:nsegs_max) )
835       ALLOCATE( thrust_seg(1:nsegs_max) )
836       ALLOCATE( torque_seg_y(1:nsegs_max) )
837       ALLOCATE( torque_seg_z(1:nsegs_max) )
[1839]838       ALLOCATE( turb_cd(1:nsegs_max) )
839       ALLOCATE( turb_cl(1:nsegs_max) )
[1819]840       ALLOCATE( vrel(1:nsegs_max) )
841       ALLOCATE( vtheta(1:nsegs_max) )
842
843!
844!--    Allocate 2D arrays (dimension = number of rotor rings and segments)
845       ALLOCATE( rbx(1:nrings_max,1:nsegs_max) )
846       ALLOCATE( rby(1:nrings_max,1:nsegs_max) )
847       ALLOCATE( rbz(1:nrings_max,1:nsegs_max) )
848       ALLOCATE( thrust_ring(1:nrings_max,1:nsegs_max) )
849       ALLOCATE( torque_ring_y(1:nrings_max,1:nsegs_max) )
850       ALLOCATE( torque_ring_z(1:nrings_max,1:nsegs_max) )
851
852!
853!--    Allocate additional 2D arrays
854       ALLOCATE( rotx(1:nturbines,1:3) )
855       ALLOCATE( roty(1:nturbines,1:3) )
856       ALLOCATE( rotz(1:nturbines,1:3) )
857
858!
859!--    Allocate 3D arrays (dimension = number of grid points)
[1912]860       ALLOCATE( nac_cd_surf(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
861       ALLOCATE( rot_tend_x(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
862       ALLOCATE( rot_tend_y(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
863       ALLOCATE( rot_tend_z(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1819]864       ALLOCATE( thrust(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
865       ALLOCATE( torque_y(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
866       ALLOCATE( torque_z(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1912]867       ALLOCATE( tow_cd_surf(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
[1819]868
869!
870!--    Allocate additional 3D arrays
871       ALLOCATE( u_int(1:nturbines,1:nrings_max,1:nsegs_max) )
872       ALLOCATE( u_int_1_l(1:nturbines,1:nrings_max,1:nsegs_max) )
873       ALLOCATE( v_int(1:nturbines,1:nrings_max,1:nsegs_max) )
874       ALLOCATE( v_int_1_l(1:nturbines,1:nrings_max,1:nsegs_max) )
875       ALLOCATE( w_int(1:nturbines,1:nrings_max,1:nsegs_max) )
876       ALLOCATE( w_int_1_l(1:nturbines,1:nrings_max,1:nsegs_max) )
877
878!
879!--    All of the arrays are initialized with a value of zero:
880       i_hub(:)                 = 0
881       i_smear(:)               = 0
882       j_hub(:)                 = 0
883       j_smear(:)               = 0
884       k_hub(:)                 = 0
885       k_smear(:)               = 0
[1912]886       
[1819]887       torque_total(:)          = 0.0_wp
[1912]888       thrust_rotor(:)          = 0.0_wp
[1819]889
[2563]890       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
891          omega_gen(:)             = 0.0_wp
892          omega_gen_old(:)         = 0.0_wp
893          omega_gen_f(:)           = 0.0_wp
894          omega_gen_f_old(:)       = 0.0_wp
895          pitch_add_old(:)         = 0.0_wp
896          torque_gen(:)            = 0.0_wp
897          torque_gen_old(:)        = 0.0_wp
898       ENDIF
899
[1819]900       yawdir(:)                = 0.0_wp
[3069]901       wdir_l(:)                = 0.0_wp
[1819]902       wdir(:)                  = 0.0_wp
903       u_inflow(:)              = 0.0_wp
[3069]904       u_inflow_l(:)            = 0.0_wp
905       phi_yaw_l(:)             = 0.0_wp
[1819]906
907!
908!--    Allocate 1D arrays (dimension = number of rotor segments)
909       alpha_attack(:)          = 0.0_wp
910       chord(:)                 = 0.0_wp
911       phi_rel(:)               = 0.0_wp
912       thrust_seg(:)            = 0.0_wp
913       torque_seg_y(:)          = 0.0_wp
914       torque_seg_z(:)          = 0.0_wp
[1864]915       turb_cd(:)               = 0.0_wp
916       turb_cl(:)               = 0.0_wp
[1819]917       vrel(:)                  = 0.0_wp
918       vtheta(:)                = 0.0_wp
919
920       rbx(:,:)                 = 0.0_wp
921       rby(:,:)                 = 0.0_wp
922       rbz(:,:)                 = 0.0_wp
923       thrust_ring(:,:)         = 0.0_wp
924       torque_ring_y(:,:)       = 0.0_wp
925       torque_ring_z(:,:)       = 0.0_wp
926
927       rotx(:,:)                = 0.0_wp
928       roty(:,:)                = 0.0_wp
929       rotz(:,:)                = 0.0_wp
930
[1912]931       nac_cd_surf(:,:,:)       = 0.0_wp
932       rot_tend_x(:,:,:)        = 0.0_wp
933       rot_tend_y(:,:,:)        = 0.0_wp
934       rot_tend_z(:,:,:)        = 0.0_wp
[1819]935       thrust(:,:,:)            = 0.0_wp
936       torque_y(:,:,:)          = 0.0_wp
937       torque_z(:,:,:)          = 0.0_wp
[1912]938       tow_cd_surf(:,:,:)       = 0.0_wp
[1819]939
940       u_int(:,:,:)             = 0.0_wp
941       u_int_1_l(:,:,:)         = 0.0_wp
942       v_int(:,:,:)             = 0.0_wp
943       v_int_1_l(:,:,:)         = 0.0_wp
944       w_int(:,:,:)             = 0.0_wp
945       w_int_1_l(:,:,:)         = 0.0_wp
946
947
[1839]948    END SUBROUTINE wtm_init_arrays
[1819]949
950
951!------------------------------------------------------------------------------!
952! Description:
953! ------------
[1839]954!> Initialization of the wind turbine model
[1819]955!------------------------------------------------------------------------------!
[1839]956    SUBROUTINE wtm_init
[1819]957
[1839]958   
[3065]959       USE control_parameters,                                                 &
960           ONLY:  dz_stretch_level_start
961   
[1819]962       IMPLICIT NONE
963
964       INTEGER(iwp) ::  i  !< running index
965       INTEGER(iwp) ::  j  !< running index
966       INTEGER(iwp) ::  k  !< running index
[1864]967       
[1819]968!
[1864]969!--    Help variables for the smearing function       
970       REAL(wp) ::  eps_kernel       !<       
971       
[1839]972!
[1864]973!--    Help variables for calculation of the tower drag       
974       INTEGER(iwp) ::  tower_n      !<
975       INTEGER(iwp) ::  tower_s      !<
[1839]976!
[1864]977!--    Help variables for the calulaction of the nacelle drag
978       INTEGER(iwp) ::  i_ip         !<
979       INTEGER(iwp) ::  i_ipg        !<
980       
981       REAL(wp) ::  yvalue               
982       REAL(wp) ::  dy_int           !<
983       REAL(wp) ::  dz_int           !<
984       
985       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: circle_points  !<
986             
987       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: index_nacb       !<
988       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: index_nacl       !<
989       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: index_nacr       !<
990       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: index_nact       !<
991       
992       ALLOCATE( index_nacb(1:nturbines) )
993       ALLOCATE( index_nacl(1:nturbines) )
994       ALLOCATE( index_nacr(1:nturbines) )
995       ALLOCATE( index_nact(1:nturbines) )
[1819]996
[1839]997!
[1819]998!------------------------------------------------------------------------------!
[1839]999!--    Calculation of parameters for the regularization kernel
1000!--    (smearing of the forces)
[1819]1001!------------------------------------------------------------------------------!
1002!
[1839]1003!--    In the following, some of the required parameters for the smearing will
1004!--    be calculated:
[1819]1005
[1839]1006!--    The kernel is set equal to twice the grid spacing which has turned out to
1007!--    be a reasonable value (see e.g. Troldborg et al. (2013), Wind Energy,
[1819]1008!--    DOI: 10.1002/we.1608):
1009       eps_kernel = 2.0_wp * dx
1010!
[1839]1011!--    The zero point (eps_min) of the polynomial function must be the following
1012!--    if the integral of the polynomial function (for values < eps_min) shall
1013!--    be equal to the integral of the Gaussian function used before:
1014       eps_min = ( 105.0_wp / 32.0_wp )**( 1.0_wp / 3.0_wp ) *                 &
1015                 pi**( 1.0_wp / 6.0_wp ) * eps_kernel
[1819]1016!
[3065]1017!--    Stretching (non-uniform grid spacing) is not considered in the wind
1018!--    turbine model. Therefore, vertical stretching has to be applied above
1019!--    the area where the wtm is active. ABS (...) is required because the
1020!--    default value of dz_stretch_level_start is -9999999.9_wp (negative).
[3174]1021       IF ( ABS( dz_stretch_level_start(1) ) <= MAXVAL(rcz(1:nturbines)) +     &
1022                                                MAXVAL(rr(1:nturbines)) +      &
1023                                                eps_min)  THEN
[3065]1024          WRITE( message_string, * ) 'The lowest level where vertical ',       &
1025                                     'stretching is applied &have to be ',     &
[3174]1026                                     'greater than ',MAXVAL(rcz(1:nturbines)) +&
1027                                      MAXVAL(rr(1:nturbines)) + eps_min
[3066]1028          CALL message( 'wtm_init', 'PA0484', 1, 2, 0, 6, 0 )
[3065]1029       ENDIF 
1030!
[1819]1031!--    Square of eps_min:
1032       eps_min2 = eps_min**2
1033!
1034!--    Parameters in the polynomial function:
[1864]1035       pol_a = 1.0_wp / eps_min**4
1036       pol_b = 2.0_wp / eps_min**2
[1819]1037!
[1839]1038!--    Normalization factor which is the inverse of the integral of the smearing
1039!--    function:
1040       eps_factor = 105.0_wp / ( 32.0_wp * pi * eps_min**3 )
1041       
[1864]1042!--    Change tilt angle to rad:
1043       tilt = tilt * pi / 180.0_wp
1044     
[1819]1045!
[1864]1046!--    Change yaw angle to rad:
[2563]1047       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
1048          phi_yaw(:) = phi_yaw(:) * pi / 180.0_wp
1049       ENDIF
[1819]1050
[1864]1051
[1819]1052       DO inot = 1, nturbines
1053!
[1864]1054!--       Rotate the rotor coordinates in case yaw and tilt are defined
1055          CALL wtm_rotate_rotor( inot )
[1819]1056         
1057!
1058!--       Determine the indices of the hub height
1059          i_hub(inot) = INT(   rcx(inot)                 / dx )
1060          j_hub(inot) = INT( ( rcy(inot) + 0.5_wp * dy ) / dy )
[3065]1061          k_hub(inot) = INT( ( rcz(inot) + 0.5_wp * dz(1) ) / dz(1) )
[1819]1062
1063!
1064!--       Determining the area to which the smearing of the forces is applied.
[1839]1065!--       As smearing now is effectively applied only for distances smaller than
1066!--       eps_min, the smearing area can be further limited and regarded as a
1067!--       function of eps_min:
[1819]1068          i_smear(inot) = CEILING( ( rr(inot) + eps_min ) / dx )
1069          j_smear(inot) = CEILING( ( rr(inot) + eps_min ) / dy )
[3065]1070          k_smear(inot) = CEILING( ( rr(inot) + eps_min ) / dz(1) )
[1864]1071       
[1819]1072       ENDDO
1073
1074!
[2792]1075!--    Call the wtm_init_speed_control subroutine and calculate the local
1076!--    omega_rot for the respective processor.
1077       IF ( speed_control)  THEN
1078       
1079          CALL wtm_speed_control
1080
1081          IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
1082
1083             DO inot = 1, nturbines
1084
1085                IF ( nxl > i_hub(inot) ) THEN
1086                   torque_gen(inot) = 0.0_wp
1087                   omega_gen_f(inot) = 0.0_wp
1088                   omega_rot_l(inot) = 0.0_wp
1089                ENDIF
1090
1091                IF ( nxr < i_hub(inot) ) THEN
1092                   torque_gen(inot) = 0.0_wp
1093                   omega_gen_f(inot) = 0.0_wp
1094                   omega_rot_l(inot) = 0.0_wp
1095                ENDIF
1096
1097                IF ( nys > j_hub(inot) ) THEN
1098                   torque_gen(inot) = 0.0_wp
1099                   omega_gen_f(inot) = 0.0_wp
1100                   omega_rot_l(inot) = 0.0_wp
1101                ENDIF
1102
1103                IF ( nyn < j_hub(inot) ) THEN
1104                   torque_gen(inot) = 0.0_wp
1105                   omega_gen_f(inot) = 0.0_wp
1106                   omega_rot_l(inot) = 0.0_wp
1107                ENDIF
1108
1109                IF ( ( nxl <= i_hub(inot) ) .AND. ( nxr >= i_hub(inot) ) ) THEN
1110                   IF ( ( nys <= j_hub(inot) ) .AND. ( nyn >= j_hub(inot) ) ) THEN
1111
1112                      omega_rot_l(inot) = omega_gen(inot) / gear_ratio
1113
1114                   ENDIF
1115                ENDIF
1116
1117             END DO
1118
1119          ENDIF
1120
1121       ENDIF
1122
1123!
[1819]1124!------------------------------------------------------------------------------!
[1839]1125!--    Determine the area within each grid cell that overlaps with the area
1126!--    of the nacelle and the tower (needed for calculation of the forces)
[1819]1127!------------------------------------------------------------------------------!
1128!
1129!--    Note: so far this is only a 2D version, in that the mean flow is
1130!--    perpendicular to the rotor area.
1131
1132!
1133!--    Allocation of the array containing information on the intersection points
1134!--    between rotor disk and the numerical grid:
1135       upper_end = ( ny + 1 ) * 10000 
1136
1137       ALLOCATE( circle_points(1:2,1:upper_end) )
[1839]1138       
1139       circle_points(:,:) = 0.0_wp
[1819]1140
[1839]1141       
1142       DO inot = 1, nturbines                     ! loop over number of turbines
[1819]1143!
[1839]1144!--       Determine the grid index (u-grid) that corresponds to the location of
1145!--       the rotor center (reduces the amount of calculations in the case that
1146!--       the mean flow is perpendicular to the rotor area):
[1819]1147          i = i_hub(inot)
1148
1149!
[1839]1150!--       Determine the left and the right edge of the nacelle (corresponding
1151!--       grid point indices):
[1819]1152          index_nacl(inot) = INT( ( rcy(inot) - rnac(inot) + 0.5_wp * dy ) / dy )
1153          index_nacr(inot) = INT( ( rcy(inot) + rnac(inot) + 0.5_wp * dy ) / dy )
1154!
[1839]1155!--       Determine the bottom and the top edge of the nacelle (corresponding
1156!--       grid point indices).The grid point index has to be increased by 1, as
1157!--       the first level for the u-component (index 0) is situated below the
1158!--       surface. All points between z=0 and z=dz/s would already be contained
1159!--       in grid box 1.
[3065]1160          index_nacb(inot) = INT( ( rcz(inot) - rnac(inot) ) / dz(1) ) + 1
1161          index_nact(inot) = INT( ( rcz(inot) + rnac(inot) ) / dz(1) ) + 1
[1819]1162
1163!
1164!--       Determine the indices of the grid boxes containing the left and
[1864]1165!--       the right boundaries of the tower:
[1819]1166          tower_n = ( rcy(inot) + 0.5_wp * dtow(inot) - 0.5_wp * dy ) / dy
1167          tower_s = ( rcy(inot) - 0.5_wp * dtow(inot) - 0.5_wp * dy ) / dy
1168
1169!
1170!--       Determine the fraction of the grid box area overlapping with the tower
[1864]1171!--       area and multiply it with the drag of the tower:
[1839]1172          IF ( ( nxlg <= i )  .AND.  ( nxrg >= i ) )  THEN
[1819]1173
1174             DO  j = nys, nyn
1175!
[1839]1176!--             Loop from south to north boundary of tower
1177                IF ( ( j >= tower_s )  .AND.  ( j <= tower_n ) )  THEN
1178
[1819]1179                   DO  k = nzb, nzt
1180
1181                      IF ( k == k_hub(inot) )  THEN
1182                         IF ( tower_n - tower_s >= 1 )  THEN
[1839]1183!
[1819]1184!--                      leftmost and rightmost grid box:
1185                            IF ( j == tower_s )  THEN
[1912]1186                               tow_cd_surf(k,j,i) = ( rcz(inot) -              &
[3065]1187                                    ( k_hub(inot) * dz(1) - 0.5_wp * dz(1) ) )*& ! extension in z-direction
[1912]1188                                  ( ( tower_s + 1.0_wp + 0.5_wp ) * dy    -    &
1189                                    ( rcy(inot) - 0.5_wp * dtow(inot) ) ) *    & ! extension in y-direction
1190                                  turb_cd_tower(inot)
[1819]1191                            ELSEIF ( j == tower_n )  THEN
[1912]1192                               tow_cd_surf(k,j,i) = ( rcz(inot)            -   &
[3065]1193                                    ( k_hub(inot) * dz(1) - 0.5_wp * dz(1) ) )*& ! extension in z-direction
[1912]1194                                  ( ( rcy(inot) + 0.5_wp * dtow(inot) )   -    &
1195                                    ( tower_n + 0.5_wp ) * dy )           *    & ! extension in y-direction
1196                                  turb_cd_tower(inot)
[1819]1197!
1198!--                         grid boxes inbetween
[1912]1199!--                         (where tow_cd_surf = grid box area):
[1819]1200                            ELSE
[1912]1201                               tow_cd_surf(k,j,i) = ( rcz(inot) -              &
[3065]1202                                    ( k_hub(inot) * dz(1) - 0.5_wp * dz(1) ) )*&
[1912]1203                                    dy * turb_cd_tower(inot)
[1819]1204                            ENDIF
1205!
1206!--                      tower lies completely within one grid box:
1207                         ELSE
[3065]1208                            tow_cd_surf(k,j,i) = ( rcz(inot) - ( k_hub(inot) * &
1209                                       dz(1) - 0.5_wp * dz(1) ) ) *            &
[1912]1210                                       dtow(inot) * turb_cd_tower(inot)
[1819]1211                         ENDIF
[1839]1212!
1213!--                  In case that k is smaller than k_hub the following actions
1214!--                  are carried out:
[1819]1215                      ELSEIF ( k < k_hub(inot) )  THEN
1216                     
[1839]1217                         IF ( ( tower_n - tower_s ) >= 1 )  THEN
1218!
[1819]1219!--                         leftmost and rightmost grid box:
1220                            IF ( j == tower_s )  THEN                         
[3065]1221                               tow_cd_surf(k,j,i) = dz(1) * (                  &
[1839]1222                                      ( tower_s + 1 + 0.5_wp ) * dy         -  &
1223                                      ( rcy(inot) - 0.5_wp * dtow(inot) )      &
[1912]1224                                                        ) * turb_cd_tower(inot)
[1819]1225                            ELSEIF ( j == tower_n )  THEN
[3065]1226                               tow_cd_surf(k,j,i) = dz(1) * (                  &
[1839]1227                                      ( rcy(inot) + 0.5_wp * dtow(inot) )   -  &
1228                                      ( tower_n + 0.5_wp ) * dy                &
[1912]1229                                                         ) * turb_cd_tower(inot)
[1839]1230!
1231!--                         grid boxes inbetween
[1912]1232!--                         (where tow_cd_surf = grid box area):
[1819]1233                            ELSE
[3065]1234                               tow_cd_surf(k,j,i) = dz(1) * dy *               &
1235                                                    turb_cd_tower(inot)
[1819]1236                            ENDIF
[1839]1237!
[1819]1238!--                         tower lies completely within one grid box:
1239                         ELSE
[3065]1240                            tow_cd_surf(k,j,i) = dz(1) * dtow(inot) *          &
[1912]1241                                                turb_cd_tower(inot)
[1839]1242                         ENDIF ! end if larger than grid box
1243
1244                      ENDIF    ! end if k == k_hub
1245
1246                   ENDDO       ! end loop over k
1247
1248                ENDIF          ! end if inside north and south boundary of tower
1249
1250             ENDDO             ! end loop over j
1251
1252          ENDIF                ! end if hub inside domain + ghostpoints
[1819]1253       
[1839]1254         
[1912]1255          CALL exchange_horiz( tow_cd_surf, nbgp )
[1819]1256
[1839]1257!
[1864]1258!--       Calculation of the nacelle area
1259!--       CAUTION: Currently disabled due to segmentation faults on the FLOW HPC
1260!--                cluster (Oldenburg)
1261!!
1262!!--       Tabulate the points on the circle that are required in the following for
1263!!--       the calculation of the Riemann integral (node points; they are called
1264!!--       circle_points in the following):
1265!
1266!          dy_int = dy / 10000.0_wp
1267!
1268!          DO  i_ip = 1, upper_end
1269!             yvalue   = dy_int * ( i_ip - 0.5_wp ) + 0.5_wp * dy           !<--- segmentation fault
1270!             sqrt_arg = rnac(inot)**2 - ( yvalue - rcy(inot) )**2          !<--- segmentation fault
1271!             IF ( sqrt_arg >= 0.0_wp )  THEN
1272!!
1273!!--             bottom intersection point
1274!                circle_points(1,i_ip) = rcz(inot) - SQRT( sqrt_arg )
1275!!
1276!!--             top intersection point
1277!                circle_points(2,i_ip) = rcz(inot) + SQRT( sqrt_arg )       !<--- segmentation fault
1278!             ELSE
1279!                circle_points(:,i_ip) = -111111                            !<--- segmentation fault
1280!             ENDIF
1281!          ENDDO
1282!
1283!
1284!          DO  j = nys, nyn
1285!!
1286!!--          In case that the grid box is located completely outside the nacelle
1287!!--          (y) it can automatically be stated that there is no overlap between
1288!!--          the grid box and the nacelle and consequently we can set
[1912]1289!!--          nac_cd_surf(:,j,i) = 0.0:
[1864]1290!             IF ( ( j >= index_nacl(inot) )  .AND.  ( j <= index_nacr(inot) ) )  THEN
1291!                DO  k = nzb+1, nzt
1292!!
1293!!--                In case that the grid box is located completely outside the
1294!!--                nacelle (z) it can automatically be stated that there is no
1295!!--                overlap between the grid box and the nacelle and consequently
[1912]1296!!--                we can set nac_cd_surf(k,j,i) = 0.0:
[1864]1297!                   IF ( ( k >= index_nacb(inot) )  .OR.                           &
1298!                        ( k <= index_nact(inot) ) )  THEN
1299!!
1300!!--                   For all other cases Riemann integrals are calculated.
1301!!--                   Here, the points on the circle that have been determined
1302!!--                   above are used in order to calculate the overlap between the
1303!!--                   gridbox and the nacelle area (area approached by 10000
1304!!--                   rectangulars dz_int * dy_int):
1305!                      DO  i_ipg = 1, 10000
1306!                         dz_int = dz
1307!                         i_ip = j * 10000 + i_ipg
1308!!
1309!!--                      Determine the vertical extension dz_int of the circle
1310!!--                      within the current grid box:
1311!                         IF ( ( circle_points(2,i_ip) < zw(k) ) .AND.          &  !<--- segmentation fault
1312!                              ( circle_points(2,i_ip) >= zw(k-1) ) ) THEN
1313!                            dz_int = dz_int -                                  &  !<--- segmentation fault
1314!                                     ( zw(k) - circle_points(2,i_ip) )
1315!                         ENDIF
1316!                         IF ( ( circle_points(1,i_ip) <= zw(k) ) .AND.         &  !<--- segmentation fault
1317!                              ( circle_points(1,i_ip) > zw(k-1) ) ) THEN
1318!                            dz_int = dz_int -                                  &
1319!                                     ( circle_points(1,i_ip) - zw(k-1) )
1320!                         ENDIF
1321!                         IF ( zw(k-1) > circle_points(2,i_ip) ) THEN
1322!                            dz_int = 0.0_wp
1323!                         ENDIF
1324!                         IF ( zw(k) < circle_points(1,i_ip) ) THEN
1325!                            dz_int = 0.0_wp                     
1326!                         ENDIF
1327!                         IF ( ( nxlg <= i ) .AND. ( nxrg >= i ) ) THEN
[1912]1328!                            nac_cd_surf(k,j,i) = nac_cd_surf(k,j,i) +        &  !<--- segmentation fault
1329!                                                  dy_int * dz_int * turb_cd_nacelle(inot)
[1864]1330!                         ENDIF   
1331!                      ENDDO
1332!                   ENDIF
1333!                ENDDO
1334!             ENDIF
[1819]1335!
[1864]1336!          ENDDO
[1819]1337!       
[1912]1338!          CALL exchange_horiz( nac_cd_surf, nbgp )                                !<---  segmentation fault
[1819]1339
[1864]1340       ENDDO   ! end of loop over turbines
[1819]1341
[3065]1342       tow_cd_surf   = tow_cd_surf   / ( dx * dy * dz(1) )  ! Normalize tower drag
1343       nac_cd_surf = nac_cd_surf / ( dx * dy * dz(1) )      ! Normalize nacelle drag
[1819]1344
[1912]1345       CALL wtm_read_blade_tables
[1839]1346 
[1864]1347    END SUBROUTINE wtm_init
1348
1349
[1819]1350!------------------------------------------------------------------------------!
[1864]1351! Description:
1352! ------------
1353!> Read in layout of the rotor blade , the lift and drag tables
1354!> and the distribution of lift and drag tables along the blade
[1819]1355!------------------------------------------------------------------------------!
[1912]1356!
1357    SUBROUTINE wtm_read_blade_tables
[1819]1358
[1839]1359
[1864]1360       IMPLICIT NONE
1361
1362       INTEGER(iwp) ::  ii   !< running index
1363       INTEGER(iwp) ::  jj   !< running index
[1843]1364   
[1864]1365       INTEGER(iwp) ::  ierrn       !<
1366   
1367       CHARACTER(200) :: chmess     !< Read in string
[1839]1368
[1864]1369       INTEGER(iwp) ::  dlen        !< no. rows of local table
1370       INTEGER(iwp) ::  dlenbl      !< no. rows of cd, cl table
1371       INTEGER(iwp) ::  ialpha      !< table position of current alpha value
1372       INTEGER(iwp) ::  iialpha     !<
1373       INTEGER(iwp) ::  iir         !<
1374       INTEGER(iwp) ::  radres      !< radial resolution
1375       INTEGER(iwp) ::  t1          !< no. of airfoil
1376       INTEGER(iwp) ::  t2          !< no. of airfoil
1377       INTEGER(iwp) ::  trow        !<
1378       INTEGER(iwp) ::  dlenbl_int  !< no. rows of interpolated cd, cl tables
[1839]1379   
[1864]1380       REAL(wp) :: alpha_attack_i   !<
1381       REAL(wp) :: weight_a         !<
1382       REAL(wp) :: weight_b         !<
[1839]1383
[1864]1384       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: ttoint1    !<
1385       INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: ttoint2    !<
[1839]1386   
[1864]1387       REAL(wp), DIMENSION(:), ALLOCATABLE :: turb_cd_sel1   !<
1388       REAL(wp), DIMENSION(:), ALLOCATABLE :: turb_cd_sel2   !<
1389       REAL(wp), DIMENSION(:), ALLOCATABLE :: turb_cl_sel1   !<
1390       REAL(wp), DIMENSION(:), ALLOCATABLE :: turb_cl_sel2   !<
1391       REAL(wp), DIMENSION(:), ALLOCATABLE :: read_cl_cd     !< read in var array
[1839]1392             
[1864]1393       REAL(wp), DIMENSION(:), ALLOCATABLE    :: alpha_attack_tab   !<
1394       REAL(wp), DIMENSION(:), ALLOCATABLE    :: trad1              !<
1395       REAL(wp), DIMENSION(:), ALLOCATABLE    :: trad2              !<         
1396       REAL(wp), DIMENSION(:,:), ALLOCATABLE  :: turb_cd_table      !<
1397       REAL(wp), DIMENSION(:,:), ALLOCATABLE  :: turb_cl_table      !<
[1839]1398                                         
[1864]1399       ALLOCATE ( read_cl_cd(1:2*nairfoils+1) )
[1839]1400
[1864]1401!
1402!--    Read in the distribution of lift and drag tables along the blade, the
1403!--    layout of the rotor blade and the lift and drag tables:
1404
[2323]1405       OPEN ( 90, FILE='WTM_DATA', STATUS='OLD', FORM='FORMATTED', IOSTAT=ierrn )
[1864]1406
1407       IF ( ierrn /= 0 )  THEN
1408          message_string = 'file WTM_DATA does not exist'
[2322]1409          CALL message( 'wtm_init', 'PA0464', 1, 2, 0, 6, 0 )
[1864]1410       ENDIF
1411!
1412!--    Read distribution table:
1413
1414       dlen = 0
1415
[2323]1416       READ ( 90, '(3/)' )
[1864]1417
1418       rloop3: DO
[2323]1419          READ ( 90, *, IOSTAT=ierrn ) chmess
[1864]1420          IF ( ierrn < 0  .OR.  chmess == '#'  .OR.  chmess == '')  EXIT rloop3
1421          dlen = dlen + 1
1422       ENDDO rloop3
1423
1424       ALLOCATE( trad1(1:dlen), trad2(1:dlen), ttoint1(1:dlen), ttoint2(1:dlen))
1425
1426       DO jj = 1,dlen+1
[2323]1427          BACKSPACE ( 90, IOSTAT=ierrn )
[1864]1428       ENDDO
1429
1430       DO jj = 1,dlen
[2323]1431          READ ( 90, * ) trad1(jj), trad2(jj), ttoint1(jj), ttoint2(jj)
[1864]1432       ENDDO
1433
1434!
1435!--    Read layout table:
1436
[1839]1437       dlen = 0 
[1864]1438
[2323]1439       READ ( 90, '(3/)')
[1864]1440
[1843]1441       rloop1: DO
[2323]1442          READ ( 90, *, IOSTAT=ierrn ) chmess
[1864]1443          IF ( ierrn < 0  .OR.  chmess == '#'  .OR.  chmess == '')  EXIT rloop1
1444          dlen = dlen + 1
[1843]1445       ENDDO rloop1
[1864]1446
[1839]1447       ALLOCATE( lrd(1:dlen), ard(1:dlen), crd(1:dlen) )
[1864]1448       DO jj = 1, dlen+1
[2323]1449          BACKSPACE ( 90, IOSTAT=ierrn )
[1864]1450       ENDDO             
1451       DO jj = 1, dlen
[2323]1452          READ ( 90, * ) lrd(jj), ard(jj), crd(jj) 
[1839]1453       ENDDO
[1819]1454
[1864]1455!
1456!--    Read tables (turb_cl(alpha),turb_cd(alpha) for the different profiles:
[1819]1457
[1864]1458       dlen = 0
1459
[2323]1460       READ ( 90, '(3/)' )
[1864]1461
[1843]1462       rloop2: DO
[2323]1463          READ ( 90, *, IOSTAT=ierrn ) chmess
[1864]1464          IF ( ierrn < 0  .OR.  chmess == '#'  .OR.  chmess == '')  EXIT rloop2
1465          dlen = dlen + 1
1466       ENDDO rloop2 
1467
[1912]1468       ALLOCATE( alpha_attack_tab(1:dlen), turb_cl_table(1:dlen,1:nairfoils),  &
[1864]1469                 turb_cd_table(1:dlen,1:nairfoils) )
1470
1471       DO jj = 1,dlen+1
[2323]1472          BACKSPACE ( 90, IOSTAT=ierrn )
[1864]1473       ENDDO 
1474
[1839]1475       DO jj = 1,dlen
[2323]1476          READ ( 90, * ) read_cl_cd
[1864]1477          alpha_attack_tab(jj) = read_cl_cd(1)
1478          DO ii= 1, nairfoils
1479             turb_cl_table(jj,ii) = read_cl_cd(ii*2)
1480             turb_cd_table(jj,ii) = read_cl_cd(ii*2+1)
[1819]1481          ENDDO
[1864]1482
[1839]1483       ENDDO
[1864]1484
1485       dlenbl = dlen 
1486
[2323]1487       CLOSE ( 90 )
[1819]1488
[1864]1489!
[2836]1490!--    For each possible radial position (resolution: 0.1 m --> 631 values if rr(1)=63m)
1491!--    and each possible angle of attack (resolution: 0.1 degrees --> 3601 values!)
[1864]1492!--    determine the lift and drag coefficient by interpolating between the
1493!--    tabulated values of each table (interpolate to current angle of attack)
1494!--    and between the tables (interpolate to current radial position):
[1839]1495
[2836]1496       ALLOCATE( turb_cl_sel1(1:dlenbl) ) 
1497       ALLOCATE( turb_cl_sel2(1:dlenbl) ) 
1498       ALLOCATE( turb_cd_sel1(1:dlenbl) )
1499       ALLOCATE( turb_cd_sel2(1:dlenbl) )
[1819]1500
[1864]1501       radres     = INT( rr(1) * 10.0_wp ) + 1_iwp
1502       dlenbl_int = INT( 360.0_wp / accu_cl_cd_tab ) + 1_iwp
[1839]1503
[2836]1504       ALLOCATE( turb_cl_tab(1:dlenbl_int,1:radres) )
1505       ALLOCATE( turb_cd_tab(1:dlenbl_int,1:radres) )
[1864]1506
[2836]1507       DO iir = 1, radres ! loop over radius
[1864]1508
[2836]1509          cur_r = ( iir - 1_iwp ) * 0.1_wp
1510!
1511!--       Find position in table 1
1512          lct = MINLOC( ABS( trad1 - cur_r ) )
1513!             lct(1) = lct(1)
[1864]1514
[2836]1515          IF ( ( trad1(lct(1)) - cur_r ) .GT. 0.0 )  THEN
1516             lct(1) = lct(1) - 1
1517          ENDIF
[1864]1518
[2836]1519          trow = lct(1)
1520!
1521!--       Calculate weights for radius interpolation
1522          weight_a = ( trad2(trow) - cur_r ) / ( trad2(trow) - trad1(trow) )
1523          weight_b = ( cur_r - trad1(trow) ) / ( trad2(trow) - trad1(trow) )
1524          t1 = ttoint1(trow)
1525          t2 = ttoint2(trow)
[1864]1526
[2836]1527          IF ( t1 .EQ. t2 ) THEN  ! if both are the same, the weights are NaN
1528             weight_a = 0.5_wp    ! then do interpolate in between same twice
1529             weight_b = 0.5_wp    ! using 0.5 as weight
1530          ENDIF
1531
1532          IF ( t1 == 0 .AND. t2 == 0 ) THEN
1533             turb_cd_sel1 = 0.0_wp
1534             turb_cd_sel2 = 0.0_wp
1535             turb_cl_sel1 = 0.0_wp
1536             turb_cl_sel2 = 0.0_wp
1537
1538             turb_cd_tab(1,iir) = 0.0_wp  ! For -180° (iialpha=1) the values   
1539             turb_cl_tab(1,iir) = 0.0_wp  ! for each radius has to be set
1540                                          ! explicitly             
1541          ELSE
1542             turb_cd_sel1 = turb_cd_table(:,t1)
1543             turb_cd_sel2 = turb_cd_table(:,t2)
1544             turb_cl_sel1 = turb_cl_table(:,t1)
1545             turb_cl_sel2 = turb_cl_table(:,t2)
1546!
1547!--          For -180° (iialpha=1) the values for each radius has to be set
1548!--          explicitly
1549             turb_cd_tab(1,iir) = ( weight_a * turb_cd_table(1,t1) + weight_b  & 
1550                                  * turb_cd_table(1,t2) )   
1551             turb_cl_tab(1,iir) = ( weight_a * turb_cl_table(1,t1) + weight_b  & 
1552                                  * turb_cl_table(1,t2) ) 
1553          ENDIF
1554
1555          DO iialpha = 2, dlenbl_int  ! loop over angles
1556             
[1864]1557             alpha_attack_i = -180.0_wp + REAL( iialpha-1 ) * accu_cl_cd_tab
1558             ialpha = 1
[2836]1559             
[2152]1560             DO WHILE ( ( alpha_attack_i > alpha_attack_tab(ialpha) ) .AND. (ialpha <= dlen ) )
[1864]1561                ialpha = ialpha + 1
1562             ENDDO
[1819]1563
[1864]1564!
[1912]1565!--          Interpolation of lift and drag coefficiencts on fine grid of radius
1566!--          segments and angles of attack
1567             turb_cl_tab(iialpha,iir) = ( alpha_attack_tab(ialpha) -           &
1568                                          alpha_attack_i ) /                   &
[1864]1569                                        ( alpha_attack_tab(ialpha) -           &
1570                                          alpha_attack_tab(ialpha-1) ) *       &
1571                                        ( weight_a * turb_cl_sel1(ialpha-1) +  &
1572                                          weight_b * turb_cl_sel2(ialpha-1) ) +&
1573                                        ( alpha_attack_i             -         &
1574                                          alpha_attack_tab(ialpha-1) ) /       &
1575                                        ( alpha_attack_tab(ialpha) -           &
1576                                          alpha_attack_tab(ialpha-1) ) *       &
1577                                        ( weight_a * turb_cl_sel1(ialpha) +    &
1578                                          weight_b * turb_cl_sel2(ialpha) )
[1912]1579             turb_cd_tab(iialpha,iir) = ( alpha_attack_tab(ialpha) -           &
1580                                          alpha_attack_i ) /                   &
[1864]1581                                        ( alpha_attack_tab(ialpha) -           &
1582                                          alpha_attack_tab(ialpha-1) ) *       &
1583                                        ( weight_a * turb_cd_sel1(ialpha-1) +  &
1584                                          weight_b * turb_cd_sel2(ialpha-1) ) +&
1585                                        ( alpha_attack_i             -         &
1586                                          alpha_attack_tab(ialpha-1) ) /       &
1587                                        ( alpha_attack_tab(ialpha) -           &
1588                                          alpha_attack_tab(ialpha-1) ) *       &
1589                                        ( weight_a * turb_cd_sel1(ialpha) +    &
1590                                          weight_b * turb_cd_sel2(ialpha) )
[2836]1591           
[1912]1592          ENDDO   ! end loop over angles of attack
[2836]1593         
1594       ENDDO   ! end loop over radius
[1819]1595
[2836]1596
[1912]1597    END SUBROUTINE wtm_read_blade_tables
[1819]1598
1599
[1864]1600!------------------------------------------------------------------------------!
1601! Description:
1602! ------------
1603!> The projection matrix for the coordinate system of therotor disc in respect
1604!> to the yaw and tilt angle of the rotor is calculated
1605!------------------------------------------------------------------------------!
1606    SUBROUTINE wtm_rotate_rotor( inot )
[1819]1607
[1864]1608
1609       IMPLICIT NONE
1610
1611       INTEGER(iwp) :: inot
1612!
1613!--    Calculation of the rotation matrix for the application of the tilt to
1614!--    the rotors
1615       rot_eigen_rad(1) = SIN( phi_yaw(inot) )    ! x-component of the radial eigenvector
1616       rot_eigen_rad(2) = COS( phi_yaw(inot) )    ! y-component of the radial eigenvector
1617       rot_eigen_rad(3) = 0.0_wp                  ! z-component of the radial eigenvector
1618
1619       rot_eigen_azi(1) = 0.0_wp                  ! x-component of the azimuth eigenvector
1620       rot_eigen_azi(2) = 0.0_wp                  ! y-component of the azimuth eigenvector
1621       rot_eigen_azi(3) = 1.0_wp                  ! z-component of the azimuth eigenvector
1622
1623       rot_eigen_nor(1) =  COS( phi_yaw(inot) )   ! x-component of the normal eigenvector
1624       rot_eigen_nor(2) = -SIN( phi_yaw(inot) )   ! y-component of the normal eigenvector
1625       rot_eigen_nor(3) = 0.0_wp                  ! z-component of the normal eigenvector
[1839]1626   
[1864]1627!
1628!--    Calculation of the coordinate transformation matrix to apply a tilt to
1629!--    the rotor. If tilt = 0, rot_coord_trans is a unit matrix.
[1819]1630
[1912]1631       rot_coord_trans(inot,1,1) = rot_eigen_rad(1)**2                   *     &
[1864]1632                                   ( 1.0_wp - COS( tilt ) ) + COS( tilt ) 
[1912]1633       rot_coord_trans(inot,1,2) = rot_eigen_rad(1) * rot_eigen_rad(2)   *     &
1634                                   ( 1.0_wp - COS( tilt ) )              -     &
[1864]1635                                   rot_eigen_rad(3) * SIN( tilt )
[1912]1636       rot_coord_trans(inot,1,3) = rot_eigen_rad(1) * rot_eigen_rad(3)   *     &
1637                                   ( 1.0_wp - COS( tilt ) )              +     &
[1864]1638                                   rot_eigen_rad(2) * SIN( tilt )
[1912]1639       rot_coord_trans(inot,2,1) = rot_eigen_rad(2) * rot_eigen_rad(1)   *     &
1640                                   ( 1.0_wp - COS( tilt ) )              +     &
[1864]1641                                   rot_eigen_rad(3) * SIN( tilt )
[1912]1642       rot_coord_trans(inot,2,2) = rot_eigen_rad(2)**2                   *     &
[1864]1643                                   ( 1.0_wp - COS( tilt ) ) + COS( tilt ) 
[1912]1644       rot_coord_trans(inot,2,3) = rot_eigen_rad(2) * rot_eigen_rad(3)   *     &
1645                                   ( 1.0_wp - COS( tilt ) )              -     &
[1864]1646                                   rot_eigen_rad(1) * SIN( tilt )
[1912]1647       rot_coord_trans(inot,3,1) = rot_eigen_rad(3) * rot_eigen_rad(1)   *     &
1648                                   ( 1.0_wp - COS( tilt ) )              -     &
[1864]1649                                   rot_eigen_rad(2) * SIN( tilt )
[1912]1650       rot_coord_trans(inot,3,2) = rot_eigen_rad(3) * rot_eigen_rad(2)   *     &
1651                                   ( 1.0_wp - COS( tilt ) )              +     &
[1864]1652                                   rot_eigen_rad(1) * SIN( tilt )
[1912]1653       rot_coord_trans(inot,3,3) = rot_eigen_rad(3)**2                   *     &
[1864]1654                                   ( 1.0_wp - COS( tilt ) ) + COS( tilt )
[1839]1655
[1864]1656!
1657!--    Vectors for the Transformation of forces from the rotor's spheric
1658!--    coordinate system to the cartesian coordinate system
1659       rotx(inot,:) = MATMUL( rot_coord_trans(inot,:,:), rot_eigen_nor )
1660       roty(inot,:) = MATMUL( rot_coord_trans(inot,:,:), rot_eigen_rad )
1661       rotz(inot,:) = MATMUL( rot_coord_trans(inot,:,:), rot_eigen_azi )
1662   
1663    END SUBROUTINE wtm_rotate_rotor
[1839]1664
1665
[1819]1666!------------------------------------------------------------------------------!
1667! Description:
1668! ------------
[1839]1669!> Calculation of the forces generated by the wind turbine
[1819]1670!------------------------------------------------------------------------------!
1671    SUBROUTINE wtm_forces
1672
[1864]1673
[1819]1674       IMPLICIT NONE
1675
[2669]1676       CHARACTER (LEN=4) ::  turbine_id
[1819]1677
[1839]1678       INTEGER(iwp) ::  i, j, k          !< loop indices
1679       INTEGER(iwp) ::  inot             !< turbine loop index (turbine id)
1680       INTEGER(iwp) ::  iialpha, iir     !<
1681       INTEGER(iwp) ::  rseg, rseg_int   !<
1682       INTEGER(iwp) ::  ring, ring_int   !<
1683       INTEGER(iwp) ::  ii, jj, kk       !<
[1912]1684   
[2232]1685       REAL(wp)     ::  flag               !< flag to mask topography grid points
[1839]1686       REAL(wp)     ::  sin_rot, cos_rot   !<
1687       REAL(wp)     ::  sin_yaw, cos_yaw   !<
[1912]1688       
1689       REAL(wp) ::  aa, bb, cc, dd  !< interpolation distances
1690       REAL(wp) ::  gg              !< interpolation volume var 
1691       
1692       REAL(wp) ::  dist_u_3d, dist_v_3d, dist_w_3d  !< smearing distances
1693
1694       
[1839]1695!
[1819]1696!      Variables for pitch control
1697       REAL(wp)     ::  torque_max=0.0_wp
[1839]1698       LOGICAL      ::  pitch_sw=.FALSE.
1699
[1819]1700       INTEGER(iwp), DIMENSION(1) :: lct=0
[1839]1701       REAL(wp), DIMENSION(1)     :: rad_d=0.0_wp
[2152]1702       
1703       REAL(wp) :: tl_factor !< factor for tip loss correction
[1819]1704
1705
[1864]1706       CALL cpu_log( log_point_s(61), 'wtm_forces', 'start' )
[1819]1707
1708
1709       IF ( simulated_time >= time_turbine_on ) THEN
1710
[1864]1711!
[1819]1712!--       Set forces to zero for each new time step:
1713          thrust(:,:,:)         = 0.0_wp
1714          torque_y(:,:,:)       = 0.0_wp
1715          torque_z(:,:,:)       = 0.0_wp
1716          torque_total(:)       = 0.0_wp
[1912]1717          rot_tend_x(:,:,:)     = 0.0_wp
1718          rot_tend_y(:,:,:)     = 0.0_wp
1719          rot_tend_z(:,:,:)     = 0.0_wp
1720          thrust_rotor(:)       = 0.0_wp
[1819]1721!
1722!--       Loop over number of turbines:
1723          DO inot = 1, nturbines
1724
1725             cos_yaw = COS(phi_yaw(inot))
1726             sin_yaw = SIN(phi_yaw(inot))
1727!
[1839]1728!--          Loop over rings of each turbine:
[1819]1729             DO ring = 1, nrings(inot)
1730
1731                thrust_seg(:)   = 0.0_wp
1732                torque_seg_y(:) = 0.0_wp
1733                torque_seg_z(:) = 0.0_wp
1734!
1735!--             Determine distance between each ring (center) and the hub:
1736                cur_r = (ring - 0.5_wp) * delta_r(inot)
1737
1738!
[1839]1739!--             Loop over segments of each ring of each turbine:
[1819]1740                DO rseg = 1, nsegs(ring,inot)
1741!
[1864]1742!--                !-----------------------------------------------------------!
1743!--                !-- Determine coordinates of the ring segments            --!
1744!--                !-----------------------------------------------------------!
[1819]1745!
[1864]1746!--                Determine angle of ring segment towards zero degree angle of
1747!--                rotor system (at zero degree rotor direction vectors aligned
1748!--                with y-axis):
[1819]1749                   phi_rotor = rseg * 2.0_wp * pi / nsegs(ring,inot)
1750                   cos_rot   = COS( phi_rotor )
1751                   sin_rot   = SIN( phi_rotor )
1752
[1864]1753!--                Now the direction vectors can be determined with respect to
1754!--                the yaw and tilt angle:
[1819]1755                   re(1) = cos_rot * sin_yaw
[1839]1756                   re(2) = cos_rot * cos_yaw   
[1819]1757                   re(3) = sin_rot
1758
1759                   rote = MATMUL( rot_coord_trans(inot,:,:), re )
1760!
1761!--                Coordinates of the single segments (center points):
1762                   rbx(ring,rseg) = rcx(inot) + cur_r * rote(1)
1763                   rby(ring,rseg) = rcy(inot) + cur_r * rote(2)
1764                   rbz(ring,rseg) = rcz(inot) + cur_r * rote(3)
1765
[1864]1766!--                !-----------------------------------------------------------!
1767!--                !-- Interpolation of the velocity components from the     --!
1768!--                !-- cartesian grid point to the coordinates of each ring  --!
1769!--                !-- segment (follows a method used in the particle model) --!
1770!--                !-----------------------------------------------------------!
[1819]1771
1772                   u_int(inot,ring,rseg)     = 0.0_wp
1773                   u_int_1_l(inot,ring,rseg) = 0.0_wp
1774
1775                   v_int(inot,ring,rseg)     = 0.0_wp
1776                   v_int_1_l(inot,ring,rseg) = 0.0_wp
1777
1778                   w_int(inot,ring,rseg)     = 0.0_wp
1779                   w_int_1_l(inot,ring,rseg) = 0.0_wp
1780
1781!
1782!--                Interpolation of the u-component:
1783
1784                   ii =   rbx(ring,rseg) * ddx
1785                   jj = ( rby(ring,rseg) - 0.5_wp * dy ) * ddy
[3065]1786                   kk = ( rbz(ring,rseg) + 0.5_wp * dz(1) ) / dz(1)
[1819]1787!
[1864]1788!--                Interpolate only if all required information is available on
1789!--                the current PE:
[1839]1790                   IF ( ( ii >= nxl )  .AND.  ( ii <= nxr ) )  THEN
1791                      IF ( ( jj >= nys )  .AND.  ( jj <= nyn ) )  THEN
[1819]1792
[1839]1793                         aa = ( ( ii + 1          ) * dx - rbx(ring,rseg) ) *  &
1794                              ( ( jj + 1 + 0.5_wp ) * dy - rby(ring,rseg) )
1795                         bb = ( rbx(ring,rseg) - ii * dx )                  *  &
1796                              ( ( jj + 1 + 0.5_wp ) * dy - rby(ring,rseg) )
1797                         cc = ( ( ii+1            ) * dx - rbx(ring,rseg) ) *  &
1798                              ( rby(ring,rseg) - ( jj + 0.5_wp ) * dy )
1799                         dd = ( rbx(ring,rseg) -              ii * dx )     *  &
1800                              ( rby(ring,rseg) - ( jj + 0.5_wp ) * dy ) 
[1819]1801                         gg = dx * dy
1802
[1864]1803                         u_int_l = ( aa * u(kk,jj,ii)     +                    &
1804                                     bb * u(kk,jj,ii+1)   +                    &
1805                                     cc * u(kk,jj+1,ii)   +                    &
1806                                     dd * u(kk,jj+1,ii+1)                      &
[1819]1807                                   ) / gg
1808
[1864]1809                         u_int_u = ( aa * u(kk+1,jj,ii)     +                  &
1810                                     bb * u(kk+1,jj,ii+1)   +                  &
1811                                     cc * u(kk+1,jj+1,ii)   +                  &
1812                                     dd * u(kk+1,jj+1,ii+1)                    &
[1819]1813                                   ) / gg
1814
[1864]1815                         u_int_1_l(inot,ring,rseg) = u_int_l          +        &
[3065]1816                                     ( rbz(ring,rseg) - zu(kk) ) / dz(1) *     &
[1819]1817                                     ( u_int_u - u_int_l )
1818
1819                      ELSE
1820                         u_int_1_l(inot,ring,rseg) = 0.0_wp
1821                      ENDIF
1822                   ELSE
1823                      u_int_1_l(inot,ring,rseg) = 0.0_wp
1824                   ENDIF
1825
1826
1827!
1828!--                Interpolation of the v-component:
1829                   ii = ( rbx(ring,rseg) - 0.5_wp * dx ) * ddx
[1839]1830                   jj =   rby(ring,rseg)                 * ddy
[3065]1831                   kk = ( rbz(ring,rseg) + 0.5_wp * dz(1) ) / dz(1) 
[1819]1832!
[1864]1833!--                Interpolate only if all required information is available on
1834!--                the current PE:
[1839]1835                   IF ( ( ii >= nxl )  .AND.  ( ii <= nxr ) )  THEN
1836                      IF ( ( jj >= nys )  .AND.  ( jj <= nyn ) )  THEN
[1819]1837
[1839]1838                         aa = ( ( ii + 1 + 0.5_wp ) * dx - rbx(ring,rseg) ) *  &
1839                              ( ( jj + 1 )          * dy - rby(ring,rseg) )
1840                         bb = ( rbx(ring,rseg)     - ( ii + 0.5_wp ) * dx ) *  &
1841                              ( ( jj + 1 ) * dy          - rby(ring,rseg) )
1842                         cc = ( ( ii + 1 + 0.5_wp ) * dx - rbx(ring,rseg) ) *  &
1843                              ( rby(ring,rseg)           -        jj * dy )
1844                         dd = ( rbx(ring,rseg)     - ( ii + 0.5_wp ) * dx ) *  &
1845                              ( rby(ring,rseg)           -        jj * dy )
[1819]1846                         gg = dx * dy
1847
[1864]1848                         v_int_l = ( aa * v(kk,jj,ii)     +                    &
1849                                     bb * v(kk,jj,ii+1)   +                    &
1850                                     cc * v(kk,jj+1,ii)   +                    &
1851                                     dd * v(kk,jj+1,ii+1)                      &
[1819]1852                                   ) / gg
1853
[1864]1854                         v_int_u = ( aa * v(kk+1,jj,ii)     +                  &
1855                                     bb * v(kk+1,jj,ii+1)   +                  &
1856                                     cc * v(kk+1,jj+1,ii)   +                  &
1857                                     dd * v(kk+1,jj+1,ii+1)                    &
[1819]1858                                  ) / gg
1859
[1864]1860                         v_int_1_l(inot,ring,rseg) = v_int_l +                 &
[3065]1861                                     ( rbz(ring,rseg) - zu(kk) ) / dz(1) *     &
[1819]1862                                     ( v_int_u - v_int_l )
1863
1864                      ELSE
1865                         v_int_1_l(inot,ring,rseg) = 0.0_wp
1866                      ENDIF
1867                   ELSE
1868                      v_int_1_l(inot,ring,rseg) = 0.0_wp
1869                   ENDIF
1870
1871
1872!
1873!--                Interpolation of the w-component:
1874                   ii = ( rbx(ring,rseg) - 0.5_wp * dx ) * ddx
1875                   jj = ( rby(ring,rseg) - 0.5_wp * dy ) * ddy
[3065]1876                   kk =   rbz(ring,rseg)                 / dz(1)
[1819]1877!
[1864]1878!--                Interpolate only if all required information is available on
1879!--                the current PE:
[1839]1880                   IF ( ( ii >= nxl )  .AND.  ( ii <= nxr ) )  THEN
1881                      IF ( ( jj >= nys )  .AND.  ( jj <= nyn ) )  THEN
[1819]1882
[1839]1883                         aa = ( ( ii + 1 + 0.5_wp ) * dx - rbx(ring,rseg) ) *  &
1884                              ( ( jj + 1 + 0.5_wp ) * dy - rby(ring,rseg) )
1885                         bb = ( rbx(ring,rseg)     - ( ii + 0.5_wp ) * dx ) *  &
1886                              ( ( jj + 1 + 0.5_wp ) * dy - rby(ring,rseg) )
1887                         cc = ( ( ii + 1 + 0.5_wp ) * dx - rbx(ring,rseg) ) *  &
1888                              ( rby(ring,rseg)     - ( jj + 0.5_wp ) * dy )
1889                         dd = ( rbx(ring,rseg)     - ( ii + 0.5_wp ) * dx ) *  &
1890                              ( rby(ring,rseg)     - ( jj + 0.5_wp ) * dy )
[1819]1891                         gg = dx * dy
1892
[1864]1893                         w_int_l = ( aa * w(kk,jj,ii)     +                    &
1894                                     bb * w(kk,jj,ii+1)   +                    &
1895                                     cc * w(kk,jj+1,ii)   +                    &
1896                                     dd * w(kk,jj+1,ii+1)                      &
[1819]1897                                   ) / gg
1898
[1864]1899                         w_int_u = ( aa * w(kk+1,jj,ii)     +                  &
1900                                     bb * w(kk+1,jj,ii+1)   +                  &
1901                                     cc * w(kk+1,jj+1,ii)   +                  &
1902                                     dd * w(kk+1,jj+1,ii+1)                    &
[1819]1903                                    ) / gg
1904
[1864]1905                         w_int_1_l(inot,ring,rseg) = w_int_l +                 &
[3065]1906                                     ( rbz(ring,rseg) - zw(kk) ) / dz(1) *     &
[1819]1907                                     ( w_int_u - w_int_l )
1908                      ELSE
1909                         w_int_1_l(inot,ring,rseg) = 0.0_wp
1910                      ENDIF
1911                   ELSE
1912                      w_int_1_l(inot,ring,rseg) = 0.0_wp
1913                   ENDIF
1914
1915                ENDDO
1916             ENDDO
1917
1918          ENDDO
1919
1920!
1921!--       Exchange between PEs (information required on each PE):
1922#if defined( __parallel )
[1839]1923          CALL MPI_ALLREDUCE( u_int_1_l, u_int, nturbines * MAXVAL(nrings) *   &
1924                              MAXVAL(nsegs), MPI_REAL, MPI_SUM, comm2d, ierr )
1925          CALL MPI_ALLREDUCE( v_int_1_l, v_int, nturbines * MAXVAL(nrings) *   &
1926                              MAXVAL(nsegs), MPI_REAL, MPI_SUM, comm2d, ierr )
1927          CALL MPI_ALLREDUCE( w_int_1_l, w_int, nturbines * MAXVAL(nrings) *   &
1928                              MAXVAL(nsegs), MPI_REAL, MPI_SUM, comm2d, ierr )
[1819]1929#else
1930          u_int = u_int_1_l
1931          v_int = v_int_1_l
1932          w_int = w_int_1_l
1933#endif
1934
1935
1936!
1937!--       Loop over number of turbines:
[1912]1938
[1819]1939          DO inot = 1, nturbines
[1912]1940pit_loop: DO
[1819]1941
[1912]1942             IF ( pitch_sw )  THEN
[1839]1943                torque_total(inot) = 0.0_wp
[1912]1944                thrust_rotor(inot) = 0.0_wp
1945                pitch_add(inot)    = pitch_add(inot) + 0.25_wp
1946!                 IF ( myid == 0 ) PRINT*, 'Pitch', inot, pitch_add(inot)
1947             ELSE
1948                cos_yaw = COS(phi_yaw(inot))
1949                sin_yaw = SIN(phi_yaw(inot))
1950                IF ( pitch_control )  THEN
1951                   pitch_add(inot) = MAX(pitch_add_old(inot) - pitch_rate *    &
1952                                         dt_3d , 0.0_wp )
1953                ENDIF
[1819]1954             ENDIF
1955
[1839]1956!
1957!--          Loop over rings of each turbine:
[1819]1958             DO ring = 1, nrings(inot)
1959!
1960!--             Determine distance between each ring (center) and the hub:
1961                cur_r = (ring - 0.5_wp) * delta_r(inot)
[1839]1962!
1963!--             Loop over segments of each ring of each turbine:
[1819]1964                DO rseg = 1, nsegs(ring,inot)
1965!
[1839]1966!--                Determine angle of ring segment towards zero degree angle of
1967!--                rotor system (at zero degree rotor direction vectors aligned
1968!--                with y-axis):
[1819]1969                   phi_rotor = rseg * 2.0_wp * pi / nsegs(ring,inot)
1970                   cos_rot   = COS(phi_rotor)
1971                   sin_rot   = SIN(phi_rotor)
1972!
[1839]1973!--                Now the direction vectors can be determined with respect to
1974!--                the yaw and tilt angle:
[1819]1975                   re(1) = cos_rot * sin_yaw
1976                   re(2) = cos_rot * cos_yaw
1977                   re(3) = sin_rot
1978
[1864]1979!                  The current unit vector in azimuthal direction:                         
[1819]1980                   rea(1) = - sin_rot * sin_yaw
1981                   rea(2) = - sin_rot * cos_yaw
1982                   rea(3) =   cos_rot
1983
1984!
[1864]1985!--                To respect the yawing angle for the calculations of
1986!--                velocities and forces the unit vectors perpendicular to the
1987!--                rotor area in direction of the positive yaw angle are defined:
[1819]1988                   ren(1) =   cos_yaw
1989                   ren(2) = - sin_yaw
1990                   ren(3) = 0.0_wp
1991!
1992!--                Multiplication with the coordinate transformation matrix
[1864]1993!--                gives the final unit vector with consideration of the rotor
1994!--                tilt:
[1819]1995                   rote = MATMUL( rot_coord_trans(inot,:,:), re )
1996                   rota = MATMUL( rot_coord_trans(inot,:,:), rea )
1997                   rotn = MATMUL( rot_coord_trans(inot,:,:), ren )
1998!
1999!--                Coordinates of the single segments (center points):
2000                   rbx(ring,rseg) = rcx(inot) + cur_r * rote(1)
2001
2002                   rby(ring,rseg) = rcy(inot) + cur_r * rote(2)
2003
2004                   rbz(ring,rseg) = rcz(inot) + cur_r * rote(3)
2005
2006!
[1864]2007!--                !-----------------------------------------------------------!
2008!--                !-- Calculation of various angles and relative velocities --!
2009!--                !-----------------------------------------------------------!
[1819]2010!
[1864]2011!--                In the following the 3D-velocity field is projected its
[2553]2012!--                components perpendicular and parallel to the rotor area
[1819]2013!--                The calculation of forces will be done in the rotor-
2014!--                coordinates y' and z.
2015!--                The yaw angle will be reintroduced when the force is applied
2016!--                on the hydrodynamic equations
[1864]2017!
2018!--                Projection of the xy-velocities relative to the rotor area
2019!
[1819]2020!--                Velocity perpendicular to the rotor area:
[1864]2021                   u_rot = u_int(inot,ring,rseg)*rotn(1) +                     &
2022                   v_int(inot,ring,rseg)*rotn(2) +                             &
[1819]2023                   w_int(inot,ring,rseg)*rotn(3)
2024!
[1864]2025!--                Projection of the 3D-velocity vector in the azimuthal
2026!--                direction:
2027                   vtheta(rseg) = rota(1) * u_int(inot,ring,rseg) +            & 
2028                                  rota(2) * v_int(inot,ring,rseg) +            &
[1819]2029                                  rota(3) * w_int(inot,ring,rseg)
2030!
[1864]2031!--                Determination of the angle phi_rel between the rotor plane
2032!--                and the direction of the flow relative to the rotor:
[1819]2033
[1864]2034                   phi_rel(rseg) = ATAN( u_rot /                               &
2035                                         ( omega_rot(inot) * cur_r -           &
[1819]2036                                           vtheta(rseg) ) )
2037
2038!
[1864]2039!--                Interpolation of the local pitch angle from tabulated values
2040!--                to the current radial position:
[1819]2041
2042                   lct=minloc(ABS(cur_r-lrd))
2043                   rad_d=cur_r-lrd(lct)
2044                   
2045                   IF (cur_r == 0.0_wp) THEN
2046                      alpha_attack(rseg) = 0.0_wp
2047                   ELSE IF (cur_r >= lrd(size(ard))) THEN
[1864]2048                      alpha_attack(rseg) = ( ard(size(ard)) +                  &
2049                                             ard(size(ard)-1) ) / 2.0_wp
[1819]2050                   ELSE
[1864]2051                      alpha_attack(rseg) = ( ard(lct(1)) *  &
2052                                             ( ( lrd(lct(1)+1) - cur_r ) /     &
2053                                               ( lrd(lct(1)+1) - lrd(lct(1)) ) &
2054                                             ) ) + ( ard(lct(1)+1) *           &
2055                                             ( ( cur_r - lrd(lct(1)) ) /       &
2056                                               ( lrd(lct(1)+1) - lrd(lct(1)) ) ) )
[1819]2057                   ENDIF
2058
2059!
[1864]2060!--                In Fortran radian instead of degree is used as unit for all
2061!--                angles. Therefore, a transformation from angles given in
2062!--                degree to angles given in radian is necessary here:
2063                   alpha_attack(rseg) = alpha_attack(rseg) *                   &
[1819]2064                                        ( (2.0_wp*pi) / 360.0_wp )
2065!
[1864]2066!--                Substraction of the local pitch angle to obtain the local
2067!--                angle of attack:
[1819]2068                   alpha_attack(rseg) = phi_rel(rseg) - alpha_attack(rseg)
2069!
[1864]2070!--                Preliminary transformation back from angles given in radian
2071!--                to angles given in degree:
2072                   alpha_attack(rseg) = alpha_attack(rseg) *                   &
[1819]2073                                        ( 360.0_wp / (2.0_wp*pi) )
2074!
[1864]2075!--                Correct with collective pitch angle:
[3139]2076                   alpha_attack(rseg) = alpha_attack(rseg) - pitch_add(inot)
[1819]2077
2078!
[1864]2079!--                Determination of the magnitude of the flow velocity relative
2080!--                to the rotor:
[1912]2081                   vrel(rseg) = SQRT( u_rot**2 +                               &
2082                                      ( omega_rot(inot) * cur_r -              &
[1819]2083                                        vtheta(rseg) )**2 )
2084
2085!
[1864]2086!--                !-----------------------------------------------------------!
2087!--                !-- Interpolation of chord as well as lift and drag       --!
2088!--                !-- coefficients from tabulated values                    --!
2089!--                !-----------------------------------------------------------!
[1819]2090
2091!
[1864]2092!--                Interpolation of the chord_length from tabulated values to
2093!--                the current radial position:
[1819]2094
2095                   IF (cur_r == 0.0_wp) THEN
2096                      chord(rseg) = 0.0_wp
2097                   ELSE IF (cur_r >= lrd(size(crd))) THEN
[1864]2098                      chord(rseg) = (crd(size(crd)) + ard(size(crd)-1)) / 2.0_wp
[1819]2099                   ELSE
[1864]2100                      chord(rseg) = ( crd(lct(1)) *                            &
2101                            ( ( lrd(lct(1)+1) - cur_r ) /                      &
2102                              ( lrd(lct(1)+1) - lrd(lct(1)) ) ) ) +            &
2103                            ( crd(lct(1)+1) *                                  &
2104                            ( ( cur_r-lrd(lct(1)) ) /                          &
2105                              ( lrd(lct(1)+1) - lrd(lct(1)) ) ) )
[1819]2106                   ENDIF
2107
2108!
2109!--                Determine index of current angle of attack, needed for
[1864]2110!--                finding the appropriate interpolated values of the lift and
[2836]2111!--                drag coefficients (-180.0 degrees = 1, +180.0 degrees = 3601,
2112!--                so one index every 0.1 degrees):
[1864]2113                   iialpha = CEILING( ( alpha_attack(rseg) + 180.0_wp )        &
[2836]2114                                      * ( 1.0_wp / accu_cl_cd_tab ) ) + 1.0_wp
[1819]2115!
2116!--                Determine index of current radial position, needed for
[1864]2117!--                finding the appropriate interpolated values of the lift and
2118!--                drag coefficients (one index every 0.1 m):
[1819]2119                   iir = CEILING( cur_r * 10.0_wp )
2120!
[1864]2121!--                Read in interpolated values of the lift and drag coefficients
2122!--                for the current radial position and angle of attack:
[1839]2123                   turb_cl(rseg) = turb_cl_tab(iialpha,iir)
2124                   turb_cd(rseg) = turb_cd_tab(iialpha,iir)
[1819]2125
2126!
[1864]2127!--                Final transformation back from angles given in degree to
2128!--                angles given in radian:
2129                   alpha_attack(rseg) = alpha_attack(rseg) *                   &
[1819]2130                                        ( (2.0_wp*pi) / 360.0_wp )
2131
[2152]2132                   IF ( tl_cor )  THEN
2133                   
2134!--                  Tip loss correction following Schito
2135!--                  Schito applies the tip loss correction only to the lift force
2136!--                  Therefore, the tip loss correction is only applied to the lift
2137!--                  coefficient and not to the drag coefficient in our case
2138!--                 
2139                     tl_factor = ( 2.0 / pi ) *                                &
2140                          ACOS( EXP( -1.0 * ( 3.0 * ( rr(inot) - cur_r ) /     &
2141                          ( 2.0 * cur_r * abs( sin( phi_rel(rseg) ) ) ) ) ) )
2142                         
2143                     turb_cl(rseg)  = tl_factor * turb_cl(rseg)                                 
2144                                 
[2894]2145                   ENDIF               
[1819]2146!
2147!--                !-----------------------------------------------------!
2148!--                !-- Calculation of the forces                       --!
2149!--                !-----------------------------------------------------!
2150
2151!
[1864]2152!--                Calculate the pre_factor for the thrust and torque forces:
[1819]2153
2154                   pre_factor = 0.5_wp * (vrel(rseg)**2) * 3.0_wp *  &
2155                                chord(rseg) * delta_r(inot) / nsegs(ring,inot)
2156
2157!
[1864]2158!--                Calculate the thrust force (x-component of the total force)
2159!--                for each ring segment:
2160                   thrust_seg(rseg) = pre_factor *                             &
2161                                      ( turb_cl(rseg) * COS(phi_rel(rseg)) +   &
2162                                        turb_cd(rseg) * SIN(phi_rel(rseg)) )
[1819]2163
2164!
[1864]2165!--                Determination of the second of the additional forces acting
2166!--                on the flow in the azimuthal direction: force vector as basis
2167!--                for torque (torque itself would be the vector product of the
2168!--                radius vector and the force vector):
2169                   torque_seg = pre_factor *                                   &
2170                                ( turb_cl(rseg) * SIN(phi_rel(rseg)) -         &
[1839]2171                                  turb_cd(rseg) * COS(phi_rel(rseg)) )
[1819]2172!
2173!--                Decomposition of the force vector into two parts:
[1864]2174!--                One acting along the y-direction and one acting along the
2175!--                z-direction of the rotor coordinate system:
[1819]2176
2177                   torque_seg_y(rseg) = -torque_seg * sin_rot
2178                   torque_seg_z(rseg) =  torque_seg * cos_rot
2179
[1912]2180!
2181!--                Add the segment thrust to the thrust of the whole rotor
2182                   thrust_rotor(inot) = thrust_rotor(inot) +                   &
2183                                        thrust_seg(rseg)                   
2184                   
2185
[1819]2186                   torque_total(inot) = torque_total(inot) + (torque_seg * cur_r)
2187
[1864]2188                ENDDO   !-- end of loop over ring segments
[1819]2189
2190!
[1864]2191!--             Restore the forces into arrays containing all the segments of
2192!--             each ring:
[1819]2193                thrust_ring(ring,:)   = thrust_seg(:)
2194                torque_ring_y(ring,:) = torque_seg_y(:)
2195                torque_ring_z(ring,:) = torque_seg_z(:)
2196
2197
[1864]2198             ENDDO   !-- end of loop over rings
[1819]2199
2200
[1864]2201             CALL cpu_log( log_point_s(62), 'wtm_controller', 'start' )
[1819]2202
[1912]2203             
2204             IF ( speed_control )  THEN
2205!
2206!--             Calculation of the current generator speed for rotor speed control
2207             
2208!                                     
2209!--             The acceleration of the rotor speed is calculated from
2210!--             the force balance of the accelerating torque
2211!--             and the torque of the rotating rotor and generator
2212                om_rate = ( torque_total(inot) * air_dens * gear_eff -         &
2213                            gear_ratio * torque_gen_old(inot) ) /              &
2214                          ( inertia_rot +                                      & 
2215                            gear_ratio * gear_ratio * inertia_gen ) * dt_3d
[1819]2216
[1912]2217!
2218!--             The generator speed is given by the product of gear gear_ratio
2219!--             and rotor speed
2220                omega_gen(inot) = gear_ratio * ( omega_rot(inot) + om_rate )     
2221             
2222             ENDIF
2223             
[1864]2224             IF ( pitch_control )  THEN
[1819]2225
[1912]2226!
2227!--             If the current generator speed is above rated, the pitch is not
2228!--             saturated and the change from the last time step is within the
2229!--             maximum pitch rate, then the pitch loop is repeated with a pitch
2230!--             gain
2231                IF ( (  omega_gen(inot)  > rated_genspeed   )  .AND.           &
2232                     ( pitch_add(inot) < 25.0_wp ) .AND.                       &
2233                     ( pitch_add(inot) < pitch_add_old(inot) +                 & 
2234                       pitch_rate * dt_3d  ) ) THEN
[1864]2235                   pitch_sw = .TRUE.
[1912]2236!
2237!--                Go back to beginning of pit_loop                   
2238                   CYCLE pit_loop
[1819]2239                ENDIF
[1912]2240               
2241!
2242!--             The current pitch is saved for the next time step
2243                pitch_add_old(inot) = pitch_add(inot)
[1864]2244                pitch_sw = .FALSE.
[1819]2245             ENDIF
[1912]2246             EXIT pit_loop             
2247          ENDDO pit_loop ! Recursive pitch control loop
[1819]2248
[1864]2249
[1819]2250!
[1864]2251!--          Call the rotor speed controller
2252             
[1819]2253             IF ( speed_control )  THEN
2254!
[1864]2255!--             Find processor at i_hub, j_hub             
[1912]2256                IF ( ( nxl <= i_hub(inot) )  .AND.  ( nxr >= i_hub(inot) ) )   &
2257                   THEN
2258                   IF ( ( nys <= j_hub(inot) )  .AND.  ( nyn >= j_hub(inot) ) )&
2259                      THEN
[1864]2260                      CALL wtm_speed_control( inot )
2261                   ENDIF
[1912]2262                ENDIF
[1864]2263                               
[1819]2264             ENDIF
2265
2266
[1864]2267             CALL cpu_log( log_point_s(62), 'wtm_controller', 'stop' )
[1819]2268
[1864]2269             CALL cpu_log( log_point_s(63), 'wtm_smearing', 'start' )
[1819]2270
2271
[1864]2272!--          !-----------------------------------------------------------------!
2273!--          !--                  Regularization kernel                      --!
2274!--          !-- Smearing of the forces and interpolation to cartesian grid  --!
2275!--          !-----------------------------------------------------------------!
[1819]2276!
[1864]2277!--          The aerodynamic blade forces need to be distributed smoothly on
2278!--          several mesh points in order to avoid singular behaviour
[1819]2279!
2280!--          Summation over sum of weighted forces. The weighting factor
[1864]2281!--          (calculated in user_init) includes information on the distance
2282!--          between the center of the grid cell and the rotor segment under
2283!--          consideration
[1819]2284!
[1864]2285!--          To save computing time, apply smearing only for the relevant part
2286!--          of the model domain:
[1819]2287!
2288!--
2289!--          Calculation of the boundaries:
[1864]2290             i_smear(inot) = CEILING( ( rr(inot) * ABS( roty(inot,1) ) +       &
2291                                        eps_min ) / dx )
2292             j_smear(inot) = CEILING( ( rr(inot) * ABS( roty(inot,2) ) +       &
2293                                        eps_min ) / dy )
[1819]2294
[1864]2295             DO i = MAX( nxl, i_hub(inot) - i_smear(inot) ),                   &
[1819]2296                    MIN( nxr, i_hub(inot) + i_smear(inot) )
[1864]2297                DO j = MAX( nys, j_hub(inot) - j_smear(inot) ),                &
[1819]2298                        MIN( nyn, j_hub(inot) + j_smear(inot) )
[2232]2299!                    DO k = MAX( nzb_u_inner(j,i)+1, k_hub(inot) - k_smear(inot) ), &
2300!                                 k_hub(inot) + k_smear(inot)
2301                   DO  k = nzb+1, k_hub(inot) + k_smear(inot)
[1819]2302                      DO ring = 1, nrings(inot)
2303                         DO rseg = 1, nsegs(ring,inot)
2304!
[2232]2305!--                         Predetermine flag to mask topography
2306                            flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 1 ) )
2307     
2308!
[1819]2309!--                         Determine the square of the distance between the
2310!--                         current grid point and each rotor area segment:
[1864]2311                            dist_u_3d = ( i * dx               - rbx(ring,rseg) )**2 + &
2312                                        ( j * dy + 0.5_wp * dy - rby(ring,rseg) )**2 + &
[3065]2313                                        ( k * dz(1) - 0.5_wp * dz(1) - rbz(ring,rseg) )**2
[1864]2314                            dist_v_3d = ( i * dx + 0.5_wp * dx - rbx(ring,rseg) )**2 + &
2315                                        ( j * dy               - rby(ring,rseg) )**2 + &
[3065]2316                                        ( k * dz(1) - 0.5_wp * dz(1) - rbz(ring,rseg) )**2
[1864]2317                            dist_w_3d = ( i * dx + 0.5_wp * dx - rbx(ring,rseg) )**2 + &
2318                                        ( j * dy + 0.5_wp * dy - rby(ring,rseg) )**2 + &
[3065]2319                                        ( k * dz(1)               - rbz(ring,rseg) )**2
[1819]2320
2321!
2322!--                         3D-smearing of the forces with a polynomial function
2323!--                         (much faster than the old Gaussian function), using
2324!--                         some parameters that have been calculated in user_init.
2325!--                         The function is only similar to Gaussian function for
2326!--                         squared distances <= eps_min2:
2327                            IF ( dist_u_3d <= eps_min2 ) THEN
[2232]2328                               thrust(k,j,i) = thrust(k,j,i) +                     &
2329                                               thrust_ring(ring,rseg) *            &
2330                                               ( ( pol_a * dist_u_3d - pol_b ) *   & 
2331                                                dist_u_3d + 1.0_wp ) * eps_factor *&
2332                                                                       flag
[1819]2333                            ENDIF
2334                            IF ( dist_v_3d <= eps_min2 ) THEN
[2232]2335                               torque_y(k,j,i) = torque_y(k,j,i) +                    &
2336                                                 torque_ring_y(ring,rseg) *           &
2337                                                 ( ( pol_a * dist_v_3d - pol_b ) *    &
2338                                                  dist_v_3d + 1.0_wp ) * eps_factor * &
2339                                                                         flag
[1819]2340                            ENDIF
2341                            IF ( dist_w_3d <= eps_min2 ) THEN
[2232]2342                               torque_z(k,j,i) = torque_z(k,j,i) +                    &
2343                                                 torque_ring_z(ring,rseg) *           &
2344                                                 ( ( pol_a * dist_w_3d - pol_b ) *    &
2345                                                  dist_w_3d + 1.0_wp ) * eps_factor * &
2346                                                                         flag
[1819]2347                            ENDIF
2348
2349                         ENDDO  ! End of loop over rseg
2350                      ENDDO     ! End of loop over ring
2351             
2352!
2353!--                   Rotation of force components:
[2232]2354                      rot_tend_x(k,j,i) = rot_tend_x(k,j,i) + (                &
[1864]2355                                      thrust(k,j,i)*rotx(inot,1) +             &
2356                                      torque_y(k,j,i)*roty(inot,1) +           &
[2232]2357                                      torque_z(k,j,i)*rotz(inot,1)             &
2358                                                              ) * flag
[1819]2359                               
[2232]2360                      rot_tend_y(k,j,i) = rot_tend_y(k,j,i) + (                &
[1864]2361                                      thrust(k,j,i)*rotx(inot,2) +             &
2362                                      torque_y(k,j,i)*roty(inot,2) +           &
[2232]2363                                      torque_z(k,j,i)*rotz(inot,2)             &
2364                                                              ) * flag
[1819]2365                               
[2232]2366                      rot_tend_z(k,j,i) = rot_tend_z(k,j,i) + (                &
[1864]2367                                      thrust(k,j,i)*rotx(inot,3) +             &
2368                                      torque_y(k,j,i)*roty(inot,3) +           &
[2232]2369                                      torque_z(k,j,i)*rotz(inot,3)             &
2370                                                              ) * flag                   
[1819]2371
2372                   ENDDO        ! End of loop over k
2373                ENDDO           ! End of loop over j
2374             ENDDO              ! End of loop over i
2375
[1864]2376             CALL cpu_log( log_point_s(63), 'wtm_smearing', 'stop' )         
[1819]2377                   
[1912]2378          ENDDO                  !-- end of loop over turbines
[1819]2379
2380               
2381          IF ( yaw_control )  THEN
2382!
2383!--          Allocate arrays for yaw control at first call
2384!--          Can't be allocated before dt_3d is set
2385             IF ( start_up )  THEN
[1864]2386                WDLON = NINT( 30.0_wp / dt_3d )  ! 30s running mean array
[1819]2387                ALLOCATE( wd30(1:nturbines,1:WDLON) )
[1912]2388                wd30 = 999.0_wp                  ! Set to dummy value
[1819]2389                ALLOCATE( wd30_l(1:WDLON) )
2390               
[1864]2391                WDSHO = NINT( 2.0_wp / dt_3d )   ! 2s running mean array
[1819]2392                ALLOCATE( wd2(1:nturbines,1:WDSHO) )
[1912]2393                wd2 = 999.0_wp                   ! Set to dummy value
[1819]2394                ALLOCATE( wd2_l(1:WDSHO) )
2395                start_up = .FALSE.
2396             ENDIF         
2397
2398!
2399!--          Calculate the inflow wind speed
2400!--
2401!--          Loop over number of turbines:
2402             DO inot = 1, nturbines
2403!
2404!--             Find processor at i_hub, j_hub             
[1912]2405                IF ( ( nxl <= i_hub(inot) )  .AND.  ( nxr >= i_hub(inot) ) )   &
2406                   THEN
2407                   IF ( ( nys <= j_hub(inot) )  .AND.  ( nyn >= j_hub(inot) ) )&
2408                      THEN
[1864]2409
[1819]2410                      u_inflow_l(inot) = u(k_hub(inot),j_hub(inot),i_hub(inot))
[1864]2411
[1912]2412                      wdir_l(inot) = -1.0_wp * ATAN2(                          &
2413                         0.5_wp * ( v(k_hub(inot),j_hub(inot),i_hub(inot)+1) + &
2414                                    v(k_hub(inot),j_hub(inot),i_hub(inot)) ) , &
2415                         0.5_wp * ( u(k_hub(inot),j_hub(inot)+1,i_hub(inot)) + &
2416                                    u(k_hub(inot),j_hub(inot),i_hub(inot)) ) )
[1864]2417
2418                      CALL wtm_yawcontrol( inot )
2419
[1819]2420                      phi_yaw_l(inot) = phi_yaw(inot)
[2015]2421                     
[1819]2422                   ENDIF
2423                ENDIF
2424                   
[1864]2425             ENDDO                                 !-- end of loop over turbines
2426
2427!
[1929]2428!--          Transfer of information to the other cpus
2429#if defined( __parallel )         
[1864]2430             CALL MPI_ALLREDUCE( u_inflow_l, u_inflow, nturbines, MPI_REAL,    &
2431                                 MPI_SUM, comm2d, ierr )
2432             CALL MPI_ALLREDUCE( wdir_l, wdir, nturbines, MPI_REAL, MPI_SUM,   &
2433                                 comm2d, ierr )
2434             CALL MPI_ALLREDUCE( phi_yaw_l, phi_yaw, nturbines, MPI_REAL,      &
2435                                 MPI_SUM, comm2d, ierr )
[1929]2436#else
2437             u_inflow = u_inflow_l
2438             wdir     = wdir_l
2439             phi_yaw  = phi_yaw_l
[2015]2440             
2441             
[1929]2442#endif
[1819]2443             DO inot = 1, nturbines
[1864]2444!             
2445!--             Update rotor orientation               
2446                CALL wtm_rotate_rotor( inot )
[1819]2447
2448             ENDDO ! End of loop over turbines
2449                           
[2894]2450          ENDIF  ! end of yaw control
[1864]2451         
2452          IF ( speed_control )  THEN
2453!
2454!--          Transfer of information to the other cpus
[1912]2455!              CALL MPI_ALLREDUCE( omega_gen, omega_gen_old, nturbines,        &
2456!                                  MPI_REAL,MPI_SUM, comm2d, ierr )
[1929]2457#if defined( __parallel )   
[1864]2458             CALL MPI_ALLREDUCE( torque_gen, torque_gen_old, nturbines,        &
2459                                 MPI_REAL, MPI_SUM, comm2d, ierr )
2460             CALL MPI_ALLREDUCE( omega_rot_l, omega_rot, nturbines,            &
2461                                 MPI_REAL, MPI_SUM, comm2d, ierr )
[1912]2462             CALL MPI_ALLREDUCE( omega_gen_f, omega_gen_f_old, nturbines,      &
2463                                 MPI_REAL, MPI_SUM, comm2d, ierr )
[1929]2464#else
2465             torque_gen_old  = torque_gen
2466             omega_rot       = omega_rot_l
2467             omega_gen_f_old = omega_gen_f
2468#endif
[1864]2469           
2470          ENDIF
[1819]2471
2472          DO inot = 1, nturbines
2473
2474             IF ( myid == 0 ) THEN
2475                IF ( openfile_turb_mod(400+inot)%opened )  THEN
2476                   WRITE ( 400+inot, 106 ) simulated_time, omega_rot(inot),    &
[1912]2477                             omega_gen(inot), torque_gen_old(inot),            &
[1864]2478                             torque_total(inot), pitch_add(inot),              &
[1912]2479                             torque_gen_old(inot)*omega_gen(inot)*gen_eff,     &
[1864]2480                             torque_total(inot)*omega_rot(inot)*air_dens,      &
[1912]2481                             thrust_rotor(inot),                               & 
[1864]2482                             wdir(inot)*180.0_wp/pi,                           &
2483                             (phi_yaw(inot))*180.0_wp/pi                   
[1912]2484                             
[1819]2485                ELSE
2486
[2669]2487                   WRITE ( turbine_id,'(A2,I2.2)')  '_T', inot
2488                   OPEN ( 400+inot, FILE=( 'WTM_OUTPUT_DATA' //                &
2489                                           TRIM( coupling_char ) //            &
2490                                           turbine_id ), FORM='FORMATTED' )
[1819]2491                   WRITE ( 400+inot, 105 ) inot
2492                   WRITE ( 400+inot, 106 ) simulated_time, omega_rot(inot),    &
[1912]2493                             omega_gen(inot), torque_gen_old(inot),            &
[1864]2494                             torque_total(inot), pitch_add(inot),              &
[1912]2495                             torque_gen_old(inot)*omega_gen(inot)*gen_eff,     &
[1864]2496                             torque_total(inot)*omega_rot(inot)*air_dens,      &
[1912]2497                             thrust_rotor(inot),                               & 
[1864]2498                             wdir(inot)*180.0_wp/pi,                           &                   
2499                             (phi_yaw(inot))*180.0_wp/pi
[1819]2500                ENDIF
2501             ENDIF
2502
[1912]2503!--          Set open flag
[1819]2504             openfile_turb_mod(400+inot)%opened = .TRUE.
[1864]2505          ENDDO                                    !-- end of loop over turbines
[1819]2506
2507       ENDIF
2508
[1864]2509       CALL cpu_log( log_point_s(61), 'wtm_forces', 'stop' )
[1819]2510       
[1912]2511!
2512!--    Formats
[1819]2513       105 FORMAT ('Turbine control data for turbine ',I2,1X,':'/ &
2514              &'----------------------------------------'/ &
2515              &'   Time   RSpeed  GSpeed  ', &
[1912]2516               'GenTorque  AeroTorque  Pitch  Power(Gen)  Power(Rot)  ',       &
2517               'RotThrust  WDirection  YawOrient')
[1819]2518
[1864]2519       106 FORMAT (F9.3,2X,F7.3,2X,F7.2,2X,F9.1,3X,F9.1,1X,F6.2,2X,F10.1,2X,   &
2520                   F10.1,1X,F9.1,2X,F7.2,1X,F7.2)
[1819]2521
2522
2523    END SUBROUTINE wtm_forces
2524
2525   
[1839]2526!------------------------------------------------------------------------------!
2527! Description:
2528! ------------
2529!> Yaw controller for the wind turbine model
2530!------------------------------------------------------------------------------!
2531    SUBROUTINE wtm_yawcontrol( inot )
2532   
[1819]2533       USE kinds
[1839]2534               
2535       IMPLICIT NONE
[1819]2536     
2537       INTEGER(iwp)             :: inot
2538       INTEGER(iwp)             :: i_wd_30
2539       REAL(wp)                 :: missal
2540
2541       i_wd_30 = 0_iwp
2542
2543
[1864]2544!--    The yaw controller computes a 30s running mean of the wind direction.
2545!--    If the difference between turbine alignment and wind direction exceeds
2546!--    5°, the turbine is yawed. The mechanism stops as soon as the 2s-running
2547!--    mean of the missalignment is smaller than 0.5°.
2548!--    Attention: If the timestep during the simulation changes significantly
2549!--    the lengths of the running means change and it does not correspond to
2550!--    30s/2s anymore.
2551!--    ! Needs to be modified for these situations !
2552!--    For wind from the east, the averaging of the wind direction could cause
2553!--    problems and the yaw controller is probably flawed. -> Routine for
2554!--    averaging needs to be improved!
2555!
2556!--    Check if turbine is not yawing
[1819]2557       IF ( .NOT. doyaw(inot) )  THEN
[1843]2558!
[1864]2559!--       Write current wind direction into array
[1843]2560          wd30_l    = wd30(inot,:)
2561          wd30_l    = CSHIFT( wd30_l, SHIFT=-1 )
[1819]2562          wd30_l(1) = wdir(inot)
[1843]2563!
[1864]2564!--       Check if array is full ( no more dummies )
[1819]2565          IF ( .NOT. ANY( wd30_l == 999.) ) THEN
2566
2567             missal = SUM( wd30_l ) / SIZE( wd30_l ) - phi_yaw(inot)
2568!
[1864]2569!--          Check if turbine is missaligned by more than max_miss
[1843]2570             IF ( ABS( missal ) > max_miss )  THEN
2571!
[1864]2572!--             Check in which direction to yaw         
[1843]2573                yawdir(inot) = SIGN( 1.0_wp, missal )
[1819]2574!
[1864]2575!--             Start yawing of turbine
[1843]2576                phi_yaw(inot) = phi_yaw(inot) + yawdir(inot) * yaw_speed * dt_3d
[1819]2577                doyaw(inot) = .TRUE.
[1864]2578                wd30_l = 999.  ! fill with dummies again
[1819]2579             ENDIF
2580          ENDIF
2581         
2582          wd30(inot,:) = wd30_l
2583
2584!     
[1864]2585!--    If turbine is already yawing:
2586!--    Initialize 2 s running mean and yaw until the missalignment is smaller
2587!--    than min_miss
[1819]2588
2589       ELSE
2590!
2591!--       Initialize 2 s running mean
2592          wd2_l = wd2(inot,:)
[1864]2593          wd2_l = CSHIFT( wd2_l, SHIFT = -1 )
[1819]2594          wd2_l(1) = wdir(inot)
[1843]2595!     
[1864]2596!--       Check if array is full ( no more dummies )
2597          IF ( .NOT. ANY( wd2_l == 999.0_wp ) ) THEN
2598!
2599!--          Calculate missalignment of turbine       
[1819]2600             missal = SUM( wd2_l - phi_yaw(inot) ) / SIZE( wd2_l )
[1864]2601!
2602!--          Check if missalignment is still larger than 0.5 degree and if the
2603!--          yaw direction is still right
2604             IF ( ( ABS( missal ) > min_miss )  .AND.                          &
2605                  ( yawdir(inot) == SIGN( 1.0_wp, missal ) ) )  THEN
2606!
2607!--             Continue yawing       
2608                phi_yaw(inot) = phi_yaw(inot) + yawdir(inot) * yaw_speed * dt_3d
[1819]2609             ELSE
[1864]2610!
2611!--             Stop yawing       
[1819]2612                doyaw(inot) = .FALSE.
[1864]2613                wd2_l = 999.0_wp ! fill with dummies again
[1819]2614             ENDIF
2615          ELSE
[1864]2616!
2617!--          Continue yawing
[1843]2618             phi_yaw(inot) = phi_yaw(inot) + yawdir(inot) * yaw_speed * dt_3d
[1819]2619          ENDIF
2620     
2621          wd2(inot,:) = wd2_l
2622           
2623       ENDIF
2624     
[1839]2625    END SUBROUTINE wtm_yawcontrol 
[1819]2626
[1864]2627
[1819]2628!------------------------------------------------------------------------------!
2629! Description:
2630! ------------
[1864]2631!> Initialization of the speed control
2632!------------------------------------------------------------------------------!
2633    SUBROUTINE wtm_init_speed_control
2634
2635
2636       IMPLICIT NONE
2637
2638!
2639!--    If speed control is set, remaining variables and control_parameters for
2640!--    the control algorithm are calculated
2641!
2642!--    Calculate slope constant for region 15
2643       slope15   = ( slope2 * min_reg2 * min_reg2 ) / ( min_reg2 - min_reg15 )
2644!
2645!--    Calculate upper limit of slipage region
2646       vs_sysp   = rated_genspeed / 1.1_wp
2647!
2648!--    Calculate slope of slipage region
2649       slope25   = ( rated_power / rated_genspeed ) /                          &
2650                   ( rated_genspeed - vs_sysp )
2651!
2652!--    Calculate lower limit of slipage region
2653       min_reg25 = ( slope25 - SQRT( slope25 * ( slope25 - 4.0_wp *            &
2654                                                 slope2 * vs_sysp ) ) ) /      &
[2410]2655                   ( 2.0_wp * slope2 ) 
[1864]2656!
2657!--    Frequency for the simple low pass filter
2658       Fcorner   = 0.25_wp
2659!
2660!--    At the first timestep the torque is set to its maximum to prevent
2661!--    an overspeeding of the rotor
[2563]2662       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
2663          torque_gen_old(:) = max_torque_gen
2664       ENDIF 
[1864]2665     
2666    END SUBROUTINE wtm_init_speed_control
2667
2668
2669!------------------------------------------------------------------------------!
2670! Description:
2671! ------------
2672!> Simple controller for the regulation of the rotor speed
2673!------------------------------------------------------------------------------!
2674    SUBROUTINE wtm_speed_control( inot )
2675
2676
2677       IMPLICIT NONE
2678
[1912]2679       INTEGER(iwp)             :: inot
2680       
2681         
[1864]2682
2683!
2684!--    The controller is based on the fortran script from Jonkman
2685!--    et al. 2009 "Definition of a 5 MW Reference Wind Turbine for
2686!--    offshore system developement"
2687
2688!
2689!--    The generator speed is filtered by a low pass filter
2690!--    for the control of the generator torque       
2691       lp_coeff = EXP( -2.0_wp * 3.14_wp * dt_3d * Fcorner )
[1912]2692       omega_gen_f(inot) = ( 1.0_wp - lp_coeff ) * omega_gen(inot) + lp_coeff *&
[1864]2693                           omega_gen_f_old(inot)
2694
2695       IF ( omega_gen_f(inot) <= min_reg15 )  THEN
2696!                       
2697!--       Region 1: Generator torque is set to zero to accelerate the rotor:
2698          torque_gen(inot) = 0
2699       
2700       ELSEIF ( omega_gen_f(inot) <= min_reg2 )  THEN
2701!                       
2702!--       Region 1.5: Generator torque is increasing linearly with rotor speed:
2703          torque_gen(inot) = slope15 * ( omega_gen_f(inot) - min_reg15 )
2704                         
2705       ELSEIF ( omega_gen_f(inot) <= min_reg25 )  THEN
2706!
2707!--       Region 2: Generator torque is increased by the square of the generator
2708!--                 speed to keep the TSR optimal:
2709          torque_gen(inot) = slope2 * omega_gen_f(inot) * omega_gen_f(inot)
2710       
2711       ELSEIF ( omega_gen_f(inot) < rated_genspeed )  THEN
2712!                       
2713!--       Region 2.5: Slipage region between 2 and 3:
2714          torque_gen(inot) = slope25 * ( omega_gen_f(inot) - vs_sysp )
2715       
2716       ELSE
2717!                       
2718!--       Region 3: Generator torque is antiproportional to the rotor speed to
2719!--                 keep the power constant:
2720          torque_gen(inot) = rated_power / omega_gen_f(inot)
2721       
2722       ENDIF
2723!                       
2724!--    Calculate torque rate and confine with a max
2725       trq_rate = ( torque_gen(inot) - torque_gen_old(inot) ) / dt_3d
2726       trq_rate = MIN( MAX( trq_rate, -1.0_wp * max_trq_rate ), max_trq_rate )
2727!                       
2728!--    Calculate new gen torque and confine with max torque                         
2729       torque_gen(inot) = torque_gen_old(inot) + trq_rate * dt_3d
2730       torque_gen(inot) = MIN( torque_gen(inot), max_torque_gen )                                             
2731!
2732!--    Overwrite values for next timestep                       
[1912]2733       omega_rot_l(inot) = omega_gen(inot) / gear_ratio
[1864]2734
2735   
2736    END SUBROUTINE wtm_speed_control   
2737
2738
2739!------------------------------------------------------------------------------!
2740! Description:
2741! ------------
[1839]2742!> Application of the additional forces generated by the wind turbine on the
2743!> flow components (tendency terms)
2744!> Call for all grid points
[1819]2745!------------------------------------------------------------------------------!
2746    SUBROUTINE wtm_tendencies( component )
2747
[1839]2748   
[1819]2749       IMPLICIT NONE
2750
[1839]2751       INTEGER(iwp) ::  component   !< prognostic variable (u,v,w)
2752       INTEGER(iwp) ::  i           !< running index
2753       INTEGER(iwp) ::  j           !< running index
2754       INTEGER(iwp) ::  k           !< running index
[1819]2755
2756
2757       SELECT CASE ( component )
2758
2759       CASE ( 1 )
2760!
2761!--       Apply the x-component of the force to the u-component of the flow:
[1864]2762          IF ( simulated_time >= time_turbine_on )  THEN
[1819]2763             DO  i = nxlg, nxrg
2764                DO  j = nysg, nyng
[2553]2765                   DO  k = nzb+1, MAXVAL(k_hub) + MAXVAL(k_smear)
[1819]2766!
[1864]2767!--                   Calculate the thrust generated by the nacelle and the tower
[1912]2768                      tend_nac_x = 0.5_wp * nac_cd_surf(k,j,i) *               &
[2553]2769                                      SIGN( u(k,j,i)**2 , u(k,j,i) )     
[1912]2770                      tend_tow_x   = 0.5_wp * tow_cd_surf(k,j,i) *             &
[1819]2771                                         SIGN( u(k,j,i)**2 , u(k,j,i) ) 
[2553]2772                                               
[2232]2773                      tend(k,j,i) = tend(k,j,i) + ( - rot_tend_x(k,j,i)        &
2774                                  - tend_nac_x - tend_tow_x )                  &
2775                                      * MERGE( 1.0_wp, 0.0_wp,                 &
2776                                               BTEST( wall_flags_0(k,j,i), 1 ) )
[1819]2777                   ENDDO
2778                ENDDO
2779             ENDDO
2780          ENDIF
2781
2782       CASE ( 2 )
2783!
2784!--       Apply the y-component of the force to the v-component of the flow:
[1864]2785          IF ( simulated_time >= time_turbine_on )  THEN
[1819]2786             DO  i = nxlg, nxrg
2787                DO  j = nysg, nyng
[2553]2788                   DO  k = nzb+1, MAXVAL(k_hub) + MAXVAL(k_smear)
[1912]2789                      tend_nac_y = 0.5_wp * nac_cd_surf(k,j,i) *               &
[1819]2790                                         SIGN( v(k,j,i)**2 , v(k,j,i) )     
[1912]2791                      tend_tow_y   = 0.5_wp * tow_cd_surf(k,j,i) *             &
[1819]2792                                         SIGN( v(k,j,i)**2 , v(k,j,i) )                     
[2232]2793                      tend(k,j,i) = tend(k,j,i) + ( - rot_tend_y(k,j,i)        &
2794                                  - tend_nac_y - tend_tow_y )                  &
2795                                      * MERGE( 1.0_wp, 0.0_wp,                 &
2796                                               BTEST( wall_flags_0(k,j,i), 2 ) )
[1819]2797                   ENDDO
2798                ENDDO
2799             ENDDO
2800          ENDIF
2801
2802       CASE ( 3 )
2803!
2804!--       Apply the z-component of the force to the w-component of the flow:
[1864]2805          IF ( simulated_time >= time_turbine_on )  THEN
[1819]2806             DO  i = nxlg, nxrg
2807                DO  j = nysg, nyng
[2553]2808                   DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
[2232]2809                      tend(k,j,i) = tend(k,j,i) - rot_tend_z(k,j,i)            &
2810                                      * MERGE( 1.0_wp, 0.0_wp,                 &
2811                                               BTEST( wall_flags_0(k,j,i), 3 ) )
[1819]2812                   ENDDO
2813                ENDDO
2814             ENDDO
2815          ENDIF
2816
2817
2818       CASE DEFAULT
2819
2820          WRITE( message_string, * ) 'unknown prognostic variable: ', component
2821          CALL message( 'wtm_tendencies', 'PA04??', 1, 2, 0, 6, 0 ) 
2822
2823       END SELECT
2824
2825
2826    END SUBROUTINE wtm_tendencies
2827
2828
2829!------------------------------------------------------------------------------!
2830! Description:
2831! ------------
[1839]2832!> Application of the additional forces generated by the wind turbine on the
2833!> flow components (tendency terms)
2834!> Call for grid point i,j
[1819]2835!------------------------------------------------------------------------------!
2836    SUBROUTINE wtm_tendencies_ij( i, j, component )
2837
2838
2839       IMPLICIT NONE
2840
[1839]2841       INTEGER(iwp) ::  component   !< prognostic variable (u,v,w)
2842       INTEGER(iwp) ::  i           !< running index
2843       INTEGER(iwp) ::  j           !< running index
2844       INTEGER(iwp) ::  k           !< running index
[1819]2845
2846       SELECT CASE ( component )
2847
2848       CASE ( 1 )
2849!
2850!--       Apply the x-component of the force to the u-component of the flow:
[1839]2851          IF ( simulated_time >= time_turbine_on )  THEN
[2553]2852             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
[1819]2853!
[1839]2854!--             Calculate the thrust generated by the nacelle and the tower
[1912]2855                tend_nac_x = 0.5_wp * nac_cd_surf(k,j,i) *                     &
[1819]2856                                   SIGN( u(k,j,i)**2 , u(k,j,i) )     
[1912]2857                tend_tow_x   = 0.5_wp * tow_cd_surf(k,j,i) *                   &
[1819]2858                                   SIGN( u(k,j,i)**2 , u(k,j,i) ) 
[2232]2859                tend(k,j,i) = tend(k,j,i) + ( - rot_tend_x(k,j,i)              &
2860                            - tend_nac_x - tend_tow_x )                        &
2861                                      * MERGE( 1.0_wp, 0.0_wp,                 &
[2553]2862                                            BTEST( wall_flags_0(k,j,i), 1 ) )
[1819]2863             ENDDO
2864          ENDIF
2865
2866       CASE ( 2 )
2867!
2868!--       Apply the y-component of the force to the v-component of the flow:
[1839]2869          IF ( simulated_time >= time_turbine_on )  THEN
[2553]2870             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
[1912]2871                tend_nac_y = 0.5_wp * nac_cd_surf(k,j,i) *                     &
[1819]2872                                   SIGN( v(k,j,i)**2 , v(k,j,i) )     
[1912]2873                tend_tow_y   = 0.5_wp * tow_cd_surf(k,j,i) *                   &
[1819]2874                                   SIGN( v(k,j,i)**2 , v(k,j,i) )                     
[2232]2875                tend(k,j,i) = tend(k,j,i) + ( - rot_tend_y(k,j,i)              &
2876                            - tend_nac_y - tend_tow_y )                        &
2877                                      * MERGE( 1.0_wp, 0.0_wp,                 &
2878                                               BTEST( wall_flags_0(k,j,i), 2 ) )
[2553]2879                ENDDO
[1819]2880          ENDIF
2881
2882       CASE ( 3 )
2883!
2884!--       Apply the z-component of the force to the w-component of the flow:
[1839]2885          IF ( simulated_time >= time_turbine_on )  THEN
[2553]2886             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
[2232]2887                tend(k,j,i) = tend(k,j,i) - rot_tend_z(k,j,i)                  &
2888                                      * MERGE( 1.0_wp, 0.0_wp,                 &
2889                                               BTEST( wall_flags_0(k,j,i), 3 ) )
[1819]2890             ENDDO
2891          ENDIF
2892
2893
2894       CASE DEFAULT
2895
2896          WRITE( message_string, * ) 'unknown prognostic variable: ', component
2897          CALL message( 'wtm_tendencies', 'PA04??', 1, 2, 0, 6, 0 ) 
2898
2899       END SELECT
2900
2901
2902    END SUBROUTINE wtm_tendencies_ij
2903
2904 END MODULE wind_turbine_model_mod
Note: See TracBrowser for help on using the repository browser.