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

Last change on this file since 4467 was 4467, checked in by maronga, 4 years ago

cleanup for last wind turbine model commit

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