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

Last change on this file since 2371 was 2349, checked in by Giersch, 7 years ago

Add parameter ptich_rate to namelist and revise/add error messages

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