1
2!-----------------------------------------------------------------------
3      SUBROUTINE WAKE_U(LDB,X,Y,Z,UBYUA,DUFAC)
4!-----------------------------------------------------------------------
5!
6! --- PRIME      Version:  1.0     Level:  990726 (99207)           WAKE_U
7!                D. Strimaitis,   EARTH TECH
8!                Prepared for EPRI under contract WO3527-01
9!
10! --- PURPOSE: Calculates speed ratio u(wake)/u(ambient) as a function
11!              of location within the wake
12!
13!              Modified by B. de Foy, 26th July 1999,
14!              To set fmin as a minimum value for ubyua
15!
16! --- INPUTS:
17!              ldb - logical     - flag for debug output
18!                x - real        - downwind distance (m) from upwind
19!                                  bldg wall
20!                y - real        - crosswind distance (m) from center of
21!                                  upwind bldg wall
22!                z - real        - height (m) above ground
23!
24!     Common block /PARAMS/ variables:
25!           MXNTR, MXNW
26!     Common block /WAKEDAT/ variables:
27!           Hb, Wb, xLb, Rb, xLR
28!     Common block /DFSN/ variables:
29!           dua_ua,xdecay,xdecayi
30!
31! --- OUTPUT:
32!
33!            ubyua - real        - U(x,z)/Ua speed in wake scaled by
34!                                  ambient speed
35!            dufac - real        - Gradient in speed factor above
36!                                  Zcav
37!
38! --- WAKE_U called by:  NUMRISE, WAKE_DBG
39! --- WAKE_U calls    :  CAVITY_HT, WAKE_DIM
40!----------------------------------------------------------------------
41!
42      INCLUDE 'params.pri'
43      INCLUDE 'dfsn.pri'
44      INCLUDE 'wakedat.pri'
45
46      LOGICAL LDB
47
48! --- Misc. constants
49      DATA TWO/2.0/ , ONE/1.0/ , ZERO/0.0/
50      DATA FMIN/0.01/
51
52! --- Compute cavity height above ground, and width
53      CALL CAVITY_HT(HB,WB,XLB,RB,XLC,XLR,HR,X,ZCAV,YCAV)               !4317496
54
55! --- Compute far wake height above ground, and width
56      CALL WAKE_DIM(X,HB,WB,RB,HWAKE,WWAKE)
57
58! --- Return "null" values if point is outside wake
59      YABS = ABS(Y)
60      UBYUA = ONE
61      DUFAC = ZERO
62      IF ( Z.GE.HWAKE .OR. YABS.GE.WWAKE ) RETURN
63
64! --- Adjust "base" speed deficit dua_ua if lateral position is
65! --- beyond bldg width projection, but within the wake
66      YMIN = AMAX1(0.5*WB,WWAKE-RB/3.)                                  !4317496
67      DU_UA = DUA_UA
68      YDIFF = WWAKE - YMIN
69      IF ( YABS.GT.YMIN .AND. YDIFF.GT.ZERO )                           &
70     &     DU_UA = DUA_UA*(ONE-(YABS-YMIN)/YDIFF)
71
72! --- Scale speed deficit (Ua-U)/Ua =  du_ua in wake for
73! --- position x downwind of bldg face
74      XML = AMAX1(ZERO,X-XLB)
75      DU_UA = DU_UA*((XML+RB)/RB)**(-XDECAY)
76! --- Interpolate factor if over roof of bldg (linear)
77      IF ( X.LT.XLB ) THEN
78         XFRAC = X/XLB                                                  ! 330202
79         DU_UA = XFRAC*DU_UA
80      ENDIF
81
82! --- Compute speed factor Ucav/Ua at top of cavity
83! --- Assume that speed is constant below ZCAV, and increases linearly
84! --- with height to ambient speed at HWAKE
85      UCBYUA = AMAX1(ZERO,(ONE-TWO*HWAKE*DU_UA/(HWAKE+ZCAV)))           !4317496
86
87! --- Compute gradient in speed factor (zero below Zcav)
88      DUFAC = ZERO
89      IF ( Z.GT.ZCAV ) DUFAC = (ONE-UCBYUA)/(HWAKE-ZCAV)
90
91! --- Compute speed factor U/Ua at height z
92      ZZ = AMIN1(Z,HWAKE)
93! --- Ensure fmin as lower bound for ubyua
94      UBYUA = AMAX1(FMIN,(UCBYUA+DUFAC*(ZZ-ZCAV)))
95
96      IF ( LDB ) THEN
97         WRITE (IO6,*) 'WAKE_U         '                                !      0
98         WRITE (IO6,*) '       x,y,z = ' , X , Y , Z
99         WRITE (IO6,*) 'hwake, zcav  = ' , HWAKE , ZCAV
100         WRITE (IO6,*) 'wwake, ymin  = ' , WWAKE , YMIN
101         WRITE (IO6,*) 'du_ua, ucbyua= ' , DU_UA , UCBYUA
102         WRITE (IO6,*) 'ubyua, dufac = ' , UBYUA , DUFAC
103         WRITE (IO6,*)
104      ENDIF
105
106      CONTINUE                                                          !4317496
107      END


HyperKWIC - Version 1.00DD executed at 20:00 on 1 Mar 2018 | Personal or Academic or Evaluation User | Free for Non-Commercial, Non-Government Use