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

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

renamed wind_turbine_parameters namelist variables

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