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

Last change on this file since 4528 was 4528, checked in by oliver.maas, 4 years ago

added wind_turbine_parameters-namelist parameter smearing_kernel_size

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