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

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

Bugfixes for restart runs

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