Changeset 3832 for palm/trunk/SOURCE/wind_turbine_model_mod.f90
- Timestamp:
- Mar 28, 2019 1:16:58 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/wind_turbine_model_mod.f90
r3725 r3832 26 26 ! ----------------- 27 27 ! $Id$ 28 ! instrumented with openmp directives 29 ! 30 ! 3725 2019-02-07 10:11:02Z raasch 28 31 ! unused variables removed 29 32 ! … … 340 343 REAL(wp) :: w_int_l !< 341 344 REAL(wp) :: w_int_u !< 345 !$OMP THREADPRIVATE (cur_r, phi_rotor, pre_factor, torque_seg, u_int_l, u_int_u, u_rot, & 346 !$OMP& v_int_l, v_int_u, w_int_l, w_int_u) 342 347 ! 343 348 !- Tendencies from the nacelle and tower thrust … … 346 351 REAL(wp) :: tend_nac_y = 0.0_wp !< 347 352 REAL(wp) :: tend_tow_y = 0.0_wp !< 353 !$OMP THREADPRIVATE (tend_nac_x, tend_tow_x, tend_nac_y, tend_tow_y) 348 354 349 355 REAL(wp), DIMENSION(:), ALLOCATABLE :: alpha_attack !< … … 1731 1737 ! 1732 1738 !-- Loop over rings of each turbine: 1739 1740 !$OMP PARALLEL PRIVATE (ring, rseg, thrust_seg, torque_seg_y, torque_seg_z, sin_rot, & 1741 !$OMP& cos_rot, re, rbx, rby, rbz, ii, jj, kk, aa, bb, cc, dd, gg) 1742 !$OMP DO 1733 1743 DO ring = 1, nrings(inot) 1734 1744 … … 1919 1929 ENDDO 1920 1930 ENDDO 1931 !$OMP END PARALLEL 1921 1932 1922 1933 ENDDO … … 1960 1971 ! 1961 1972 !-- Loop over rings of each turbine: 1973 !$OMP PARALLEL PRIVATE (ring, rseg, sin_rot, cos_rot, re, rea, ren, rote, rota, rotn, & 1974 !$OMP& vtheta, phi_rel, lct, rad_d, alpha_attack, vrel, & 1975 !$OMP& chord, iialpha, iir, turb_cl, tl_factor, thrust_seg, & 1976 !$OMP& torque_seg_y, turb_cd, torque_seg_z, thrust_ring, & 1977 !$OMP& torque_ring_y, torque_ring_z) 1978 !$OMP DO 1962 1979 DO ring = 1, nrings(inot) 1963 1980 ! … … 2184 2201 ! 2185 2202 !-- Add the segment thrust to the thrust of the whole rotor 2203 !$OMP CRITICAL 2186 2204 thrust_rotor(inot) = thrust_rotor(inot) + & 2187 2205 thrust_seg(rseg) … … 2189 2207 2190 2208 torque_total(inot) = torque_total(inot) + (torque_seg * cur_r) 2209 !$OMP END CRITICAL 2191 2210 2192 2211 ENDDO !-- end of loop over ring segments … … 2201 2220 2202 2221 ENDDO !-- end of loop over rings 2222 !$OMP END PARALLEL 2203 2223 2204 2224 … … 2297 2317 eps_min ) / dy ) 2298 2318 2319 !$OMP PARALLEL PRIVATE (i, j, k, ring, rseg, flag, dist_u_3d, dist_v_3d, dist_w_3d) 2320 !$OMP DO 2299 2321 DO i = MAX( nxl, i_hub(inot) - i_smear(inot) ), & 2300 2322 MIN( nxr, i_hub(inot) + i_smear(inot) ) … … 2377 2399 ENDDO ! End of loop over j 2378 2400 ENDDO ! End of loop over i 2401 !$OMP END PARALLEL 2379 2402 2380 2403 CALL cpu_log( log_point_s(63), 'wtm_smearing', 'stop' )
Note: See TracChangeset
for help on using the changeset viewer.