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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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