1!-----------------------------------------------------------------------
2      SUBROUTINE WAKE_DBG(IO,NTR,XTR,YTR,ZTR,RTR,NOBID,HSTACK)
3!-----------------------------------------------------------------------
4!
5! --- PRIME      Version:  1.0     Level:  970812              WAKE_DBG
6!                D. Strimaitis,   EARTH TECH
7!                Prepared for EPRI under contract WO3527-01
8!
9! --- PURPOSE: Reports salient features of PRIME results to
10!              file for DEBUG purposes
11!
12! --- MODIFIED: For use with the AERMOD model.  Added hstack to calling
13!               arguments for WAKE_XSIG.
14!               R.W. Brode, PES, Inc. - 07/05/01
15!
16! --- INPUTS:
17!               io - integer     - unit for output file
18!         XTR(ntr) - real        - Downwind distance (m)
19!         YTR(ntr) - real        - Crosswind distance (m)
20!         ZTR(ntr) - real        - Plume centerline height (m)
21!         RTR(ntr) - real        - Plume radius (m)
22!            NOBID - logical     - flag for BID
23!           HSTACK - real        - height (m) of release
24!
25!     Common block /PARAMS/ variables:
26!           MXNTR, MXNW
27!     Common block /WAKEDAT/ variables:
28!           XBADJ, Hb, Wb, xLb, Rb, xLR, xLC, HR,
29!           XCAV, SZCAV, SYCAV
30!
31! --- OUTPUT: (written to file)
32!
33!          DBXB - real    - Distance (m) from upwind bldg face
34!           DBX - real    - Distance (m) from source along wind
35!           DBZ - real    - Plume centerline height above ground (m)
36!          DBHC - real    - Cavity height above ground (m)
37!          DBHW - real    - Wake height above ground (m)
38!          DBSZ - real    - Sigma-z (m)
39!          DBSY - real    - Sigma-y (m)
40!          DBUW - real    - Wind speed factor at DBZ  (u/Ua)
41!         DBRSZ - real    - Sigma-y (m) inferred from plume radius
42!       IPOSITN - integer - 1: in bldg
43!                           2: in cavity
44!                           3: in far wake
45!                           4: outside bldg influence
46!         DBSZC - real    - Sigma-z (m) for cavity source
47!         DBSYC - real    - Sigma-y (m) for cavity source
48!
49! --- WAKE_DBG called by:  PHEFF
50! --- WAKE_DBG calls    :  WAKE_XSIG, WAKE_DIM, CAVITY_HT,
51!                          POSITION, WAKE_U
52!----------------------------------------------------------------------
53!
54      INCLUDE 'params.pri'
55      INCLUDE 'wakedat.pri'
56
57      REAL XTR(NTR) , YTR(NTR) , ZTR(NTR) , RTR(NTR)
58      LOGICAL NOBID , LDB
59
60      LDB = .FALSE.                                                     !      0
61
62      DATA RT2BYPI/0.797885/
63
64! --- Write section header to file
65      WRITE (IO,*)
66      WRITE (IO,*) '------------------------------------------------'
67      WRITE (IO,*) 'PRIME Module Results for Current Source and Hour'
68      WRITE (IO,*) '          (all lengths in meters)'
69      WRITE (IO,*) '------------------------------------------------'
70      WRITE (IO,*)
71      WRITE (IO,100)
72
73 100  FORMAT ('     XB      X      Z   Hwake   Hcav    Sz     S',       &
74     &        'y   Ufac  dUfac  R->Sz   dRdx  Pos  Szcav  Sycav')
75      WRITE (IO,*)
76
77! --- Report start of cavity as first point if it lies upwind of source
78      IF ( XCAV(1).LT.0.0 ) THEN
79! ---    Set plume coordinates
80         DBX = XCAV(1)                                                  !      0
81         DBY = YTR(1)
82         DBZ = 0.0
83
84! ---    Set initial values
85         DBSZ = 0.0
86         DBSY = 0.0
87         DBHW = 0.0
88         DBHC = 0.0
89         DBRSZ = 0.0
90         DBUW = 1.0
91         IPOSITN = 4
92
93! ---    Compute related data
94         RISE = 0.0
95         XB = DBX - XBADJ
96         YB = DBY - YBADJ
97         ZB = DBZ
98         DBXB = XB
99
100! ---    Set sigmas
101         DBSZ = 0.0
102         DBSY = 0.0
103         DBSZC = SZCAV(1)
104         DBSYC = SYCAV(1)
105
106! ---    Set dr/dx of plume radius within wake region
107         DBDRDX = 0.0
108
109         IF ( XB.GE.0.0 ) THEN
110! ---       Set wake dimension along center plane from bldg
111            CALL WAKE_DIM(XB,HB,WB,RB,DBHW,DBWW)                        !      0
112
113! ---       Set cavity dimension along centerplane from bldg
114            CALL CAVITY_HT(HB,WB,XLB,RB,XLC,XLR,HR,XB,DBHC,DBWC)
115
116! ---       Set speed factor
117            CALL POSITION(XB,YB,ZB,IPOSITN)
118            DBUW = 1.0
119            IF ( IPOSITN.LT.4 ) CALL WAKE_U(LDB,XB,YB,ZB,DBUW,DBDUW)
120         ENDIF
121
122! ---    Report values
123         WRITE (IO,101) DBXB , DBX , DBZ , DBHW , DBHC , DBSZ , DBSY ,  &
124     &                  DBUW , DBDUW , DBRSZ , DBDRDX , IPOSITN ,       &
125     &                  DBSZC , DBSYC
126      ENDIF
127
128! --- Process point of release
129! --- Set plume coordinates
130      DBX = 0.0                                                         !      0
131      DBY = YTR(1)
132      DBZ = HSTACK
133
134! --- Set initial values
135      DBSZ = 0.0
136      DBSY = 0.0
137      DBHW = 0.0
138      DBHC = 0.0
139      DBRSZ = 0.0
140      DBUW = 1.0
141      IPOSITN = 4
142
143! --- Compute related data
144      RISE = DBZ - HSTACK
145      XB = DBX - XBADJ
146      YB = DBY - YBADJ
147      ZB = DBZ
148      DBXB = XB
149
150! --- Set sigmas just downwind of source
151      XZERO = 0.001
152      CALL WAKE_XSIG(XZERO,HSTACK,RISE,NOBID,DBSZ,DBSY,DBSZC,DBSYC)
153
154! --- Set dr/dx of plume radius within wake region
155      CALL WAKE_DRDX(DBX,DBDRDX)
156
157      IF ( XB.GE.0.0 ) THEN
158! ---    Set wake dimension along center plane from bldg
159         CALL WAKE_DIM(XB,HB,WB,RB,DBHW,DBWW)                           !      0
160
161! ---    Set cavity dimension along centerplane from bldg
162         CALL CAVITY_HT(HB,WB,XLB,RB,XLC,XLR,HR,XB,DBHC,DBWC)
163
164! ---    Set speed factor
165         CALL POSITION(XB,YB,ZB,IPOSITN)
166         DBUW = 1.0
167         IF ( IPOSITN.LT.4 ) CALL WAKE_U(LDB,XB,YB,ZB,DBUW,DBDUW)
168      ENDIF
169
170! --- Report values
171      WRITE (IO,101) DBXB , DBX , DBZ , DBHW , DBHC , DBSZ , DBSY ,     &
172     &               DBUW , DBDUW , DBRSZ , DBDRDX , IPOSITN , DBSZC ,  &
173     &               DBSYC
174
175! --- Now loop over entries in plume rise array
176      DO IT = 1 , NTR
177
178! ---    Set plume coordinates
179         DBX = XTR(IT)                                                  !      0
180         DBY = YTR(IT)
181         DBZ = ZTR(IT)
182         DBRSZ = RTR(IT)*RT2BYPI
183
184! ---    Set initial values
185         DBHW = 0.0
186         DBHC = 0.0
187         DBUW = 1.0
188         IPOSITN = 4
189
190! ---    Compute related data
191         RISE = DBZ - HSTACK
192         XB = DBX - XBADJ
193         YB = DBY - YBADJ
194         ZB = DBZ
195         DBXB = XB
196
197! ---    Set sigmas
198         CALL WAKE_XSIG(DBX,HSTACK,RISE,NOBID,DBSZ,DBSY,DBSZC,DBSYC)
199
200! ---    Set dr/dx of plume radius within wake region
201         CALL WAKE_DRDX(DBX,DBDRDX)
202
203         IF ( XB.GE.0.0 ) THEN
204! ---       Set wake dimension along center plane from bldg
205            CALL WAKE_DIM(XB,HB,WB,RB,DBHW,DBWW)                        !      0
206
207! ---       Set cavity dimension along centerplane from bldg
208            CALL CAVITY_HT(HB,WB,XLB,RB,XLC,XLR,HR,XB,DBHC,DBWC)
209
210! ---       Set speed factor
211            CALL POSITION(XB,YB,ZB,IPOSITN)
212            DBUW = 1.0
213            IF ( IPOSITN.LT.4 ) CALL WAKE_U(LDB,XB,YB,ZB,DBUW,DBDUW)
214         ENDIF
215
216! ---    Report values
217         WRITE (IO,101) DBXB , DBX , DBZ , DBHW , DBHC , DBSZ , DBSY ,  &
218     &                  DBUW , DBDUW , DBRSZ , DBDRDX , IPOSITN ,       &
219     &                  DBSZC , DBSYC
220
221      ENDDO
222      WRITE (IO,*)                                                      !      0
223
224      CONTINUE
225 101  FORMAT (1x,7F7.1,2F7.3,f7.1,f7.3,i4,2F7.1)
226      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