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

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

Bugfix for restart runs if the wind turbine model is used

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