Ignore:
Timestamp:
Mar 28, 2019 1:16:58 PM (5 years ago)
Author:
raasch
Message:

some routines instrumented with openmp directives, loop reordering for performance optimization

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/wind_turbine_model_mod.f90

    r3725 r3832  
    2626! -----------------
    2727! $Id$
     28! instrumented with openmp directives
     29!
     30! 3725 2019-02-07 10:11:02Z raasch
    2831! unused variables removed
    2932!
     
    340343    REAL(wp) ::  w_int_l                     !<
    341344    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)
    342347!
    343348!-  Tendencies from the nacelle and tower thrust
     
    346351    REAL(wp) ::  tend_nac_y = 0.0_wp  !<
    347352    REAL(wp) ::  tend_tow_y = 0.0_wp  !<
     353    !$OMP THREADPRIVATE (tend_nac_x, tend_tow_x, tend_nac_y, tend_tow_y)
    348354
    349355    REAL(wp), DIMENSION(:), ALLOCATABLE ::  alpha_attack !<
     
    17311737!
    17321738!--          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
    17331743             DO ring = 1, nrings(inot)
    17341744
     
    19191929                ENDDO
    19201930             ENDDO
     1931             !$OMP END PARALLEL
    19211932
    19221933          ENDDO
     
    19601971!
    19611972!--          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
    19621979             DO ring = 1, nrings(inot)
    19631980!
     
    21842201!
    21852202!--                Add the segment thrust to the thrust of the whole rotor
     2203                   !$OMP CRITICAL
    21862204                   thrust_rotor(inot) = thrust_rotor(inot) +                   &
    21872205                                        thrust_seg(rseg)                   
     
    21892207
    21902208                   torque_total(inot) = torque_total(inot) + (torque_seg * cur_r)
     2209                   !$OMP END CRITICAL
    21912210
    21922211                ENDDO   !-- end of loop over ring segments
     
    22012220
    22022221             ENDDO   !-- end of loop over rings
     2222             !$OMP END PARALLEL
    22032223
    22042224
     
    22972317                                        eps_min ) / dy )
    22982318
     2319             !$OMP PARALLEL PRIVATE (i, j, k, ring, rseg, flag, dist_u_3d, dist_v_3d, dist_w_3d)
     2320             !$OMP DO
    22992321             DO i = MAX( nxl, i_hub(inot) - i_smear(inot) ),                   &
    23002322                    MIN( nxr, i_hub(inot) + i_smear(inot) )
     
    23772399                ENDDO           ! End of loop over j
    23782400             ENDDO              ! End of loop over i
     2401             !$OMP END PARALLEL
    23792402
    23802403             CALL cpu_log( log_point_s(63), 'wtm_smearing', 'stop' )         
Note: See TracChangeset for help on using the changeset viewer.