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

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

allow for simulating up to 10 000 wind turbines

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