1!-----------------------------------------------------------------------
2      SUBROUTINE CAV_SRC(XR,YR,ZR,FQCAV0,QC,HC,YRC,ZRC,SZC,SYC,N1,N2)
3!-----------------------------------------------------------------------
4!
5! --- PRIME      Version:  1.0     Level:  970812               CAV_SRC
6!                D. Strimaitis,   EARTH TECH
7!                Prepared for EPRI under contract WO3527-01
8!
9! --- PURPOSE:  Select plume data for computing concentration at a
10!               receptor due to mass contained in / released from cavity
11!
12! --- MODIFIED: For use with the AERMOD model.  Added hc to calling
13!               arguments for WAKE_XSIG.  Also modified case where only
14!               primary source and "outside" cavity source contribute
15!               to keep "outside" cavity source in slot 3 by setting
16!               emission rate for "inside" cavity source to 0.0.
17!               R.W. Brode, PES, Inc. - 07/05/01
18!
19! --- INPUTS:
20!            XR - real    - Downwind distance (m) from stack to receptor
21!            YR - real    - Crosswind distance (m) from stack to receptor
22!            ZR - real    - Receptor height (m) above ground
23!
24!     Common block /WAKEDAT/ variables:
25!           Hb, Wb, xLb, Rb, xLC, xLR, HR,
26!           XBADJ, YBADJ, SZCAV, SYCAV, FQCAV
27!
28! --- OUTPUT:
29!
30!        FQCAV0 - real    - Fraction of plume mass rate captured
31!                           and released by cavity
32!         QC(3) - real    - Normalized emission rate (q/s) for cavity
33!                           sources --- QC(1)+QC(2)=1.0
34!         HC(3) - real    - Height (m) of cavity sources
35!        YRC(3) - real    - Crosswind distance (m) from centerline
36!                           of cavity sources to receptor
37!        ZRC(3) - real    - Receptor height (m) above cavity
38!        SZC(3) - real    - Sigma-z (m) for cavity sources
39!        SYC(3) - real    - Sigma-y (m) for cavity sources
40!         N1,N2 - integer - Index range for active sources
41!                           1,1: Primary source ONLY (no cavity source
42!                                contributions)
43!                           1,2: Primary and "outside" cavity source
44!                                contribution
45!                           1,3: Primary and both "outside" and "inside"
46!                                cavity source contributions
47!                           2,2: "outside" cavity source ONLY
48!                           2,3: Both "outside" and "inside" cavity
49!                                sources
50!                           3,3: "inside" cavity source ONLY
51!
52! ------------------------------------
53!     NOTE:  3 sources are considered:
54!                           (1)- the primary (point) source
55!                           (2)- the cavity source that dominates
56!                                "outside" of the cavity
57!                           (3)- the cavity source that dominates
58!                                "inside" of the cavity
59!            For the 2 cavity sources, array data elements are ordered:
60!                           (1)- RESERVED for primary source data
61!                           (2)- "outside" cavity source
62!                           (3)- "inside" cavity source
63!
64! --- CAV_SRC called by:  PSIMPL(HOST subroutine)
65! --- CAV_SRC calls    :  POSITION, CAVITY_HT, WAKE_XSIG
66!----------------------------------------------------------------------
67!
68      INCLUDE 'params.pri'
69      INCLUDE 'wakedat.pri'
70
71      REAL QC(3) , HC(3) , YRC(3) , ZRC(3) , SZC(3) , SYC(3)
72!JRA declaration to avoid interface error with arg 4 of WAKE_XSIG
73      LOGICAL LDB
74
75      DATA RT2PI/2.5066283/
76
77! --- Extract cavity sigmas from the first entry in the cavity arrays
78      SZCAV0 = SZCAV(1)                                                 ! 421752
79      SYCAV0 = SYCAV(1)
80
81! --- Pass mass fraction to calling program
82      FQCAV0 = FQCAV
83
84! --- Set cavity source heights to zero
85      HC(2) = 0.0
86      HC(3) = 0.0
87
88! --- Initialize cavity source mode
89! --- (0: none, 1: "outside", 2: "inside", 3: both)
90      MODE = 0
91
92      IF ( FQCAV.LE.0.0 ) THEN
93! ---    No mass in cavity
94         N1 = 1                                                         !  49568
95         N2 = 1
96         DO I = 2 , 3
97            QC(I) = 0.0                                                 !  99136
98            YRC(I) = YR
99            ZRC(I) = ZR
100            SZC(I) = SZCAV0
101            SYC(I) = SYCAV0
102         ENDDO
103      ELSE
104! ---    Find receptor location relative to center of upwind bldg face
105         XRB = XR - XBADJ                                               ! 372184
106         YRB = YR - YBADJ
107         ZRB = ZR
108         CALL POSITION(XRB,YRB,ZRB,IPOSITN)
109
110! ---    Set limits of transition zone at end of cavity
111         X115B = XLB + 1.15*XLR
112         X85B = XLB + 0.85*XLR
113! ---    Adjust relative contribution of cavity sources near end
114! ---    of cavity region
115         IF ( XRB.GE.X115B ) THEN
116! ---       Receptor well outside cavity; use only "outside" source
117            QC(2) = 1.0                                                 ! 277594
118            QC(3) = 0.0
119            MODE = 1
120         ELSEIF ( XRB.GT.X85B ) THEN
121! ---       Mix relative contribution so that they are equal at
122! ---       end of cavity
123            QC(2) = (XRB-X85B)/(X115B-X85B)                             !  17516
124            QC(3) = 1.0 - QC(2)
125            MODE = 3
126         ELSEIF ( XRB.GT.XLB ) THEN
127! ---       Receptor well within cavity; use only "inside" source
128            QC(2) = 0.0                                                 !  50522
129            QC(3) = 1.0
130            MODE = 2
131         ELSE
132! ---       Receptor upwind of trailing edge of projected bldg;
133! ---       use "inside" source, but drop mass fraction linearly
134! ---       to zero at windward face of projected bldg
135            QC(2) = 0.0                                                 !  26552
136            QC(3) = AMAX1(0.0,XRB/XLB)
137            MODE = 2
138         ENDIF
139
140         IF ( IPOSITN.EQ.4 ) THEN                                       ! 372184
141! ---       Not within wake, so drop cavity source contribution
142            MODE = 0                                                    ! 321086
143            N1 = 1
144            N2 = 1
145            DO I = 2 , 3
146               QC(I) = 0.0                                              ! 642172
147               YRC(I) = YR
148               ZRC(I) = ZR
149               SZC(I) = SZCAV0
150               SYC(I) = SYCAV0
151            ENDDO
152         ELSE
153! ---       Set receptor offset from centerline of cavity plume
154! ---       Top-hat equivalent width of cavity sigma-y
155            WTOP = SYCAV0*RT2PI                                         !  51098
156! ---       Max distance from bldg center to centerline of cavity plume
157            YBMAX = 0.5*(WB-WTOP)
158            IF ( YBMAX.LE.0.0 ) THEN
159! ---          Plume spread exceeds bldg width so cavity source is
160! ---          centered on bldg
161               YRC(2) = YRB                                             !  51098
162            ELSE
163! ---          Source location relative to center of bldg
164               YSB = -YBADJ                                             !      0
165               IF ( YSB.LT.0.0 ) THEN
166                  YRC(2) = YRB - AMAX1(YSB,-YBMAX)                      !      0
167               ELSE
168                  YRC(2) = YRB - AMIN1(YSB,YBMAX)                       !      0
169               ENDIF
170            ENDIF
171            YRC(3) = YRC(2)                                             !  51098
172
173            IF ( IPOSITN.LE.2 ) THEN
174! ---          Within cavity/bldg, so drop primary source contribution,
175! ---          and place receptor on ground
176               IF ( MODE.EQ.3 ) THEN                                    !   3572
177                  N1 = 2                                                !    262
178                  N2 = 3
179               ELSEIF ( MODE.EQ.2 ) THEN
180                  N1 = 3                                                !   3310
181                  N2 = 3
182               ELSEIF ( MODE.EQ.1 ) THEN
183                  N1 = 2                                                !      0
184                  N2 = 2
185               ENDIF
186               DO I = N1 , N2                                           !   3572
187                  ZRC(I) = 0.0                                          !   3834
188                  SZC(I) = SZCAV0
189                  SYC(I) = SYCAV0
190               ENDDO
191               IF ( (MODE.EQ.1 .OR. MODE.EQ.3) .AND. XR.GT.0.0 )        &
192     &              CALL WAKE_XSIG(XR,HC(2),0.0,LDB,DUMZ,DUMY,SZC(2),   &
193     &                             SYC(2))
194            ELSE
195! ---          Contributions from primary & possibly both cavity plumes
196               N1 = 1                                                   !  47526
197               N2 = 3
198! ---          Set pole height to height above cavity boundary
199               IF ( XRB.GE.(XLB+XLR) ) THEN
200                  ZRC(2) = ZR                                           !  44122
201               ELSE
202                  CALL CAVITY_HT(HB,WB,XLB,RB,XLC,XLR,HR,XRB,ZCAV,WCAV) !   3404
203                  ZRC(2) = AMAX1(0.0,ZR-ZCAV)
204               ENDIF
205               ZRC(3) = ZRC(2)                                          !  47526
206               IF ( MODE.EQ.2 ) THEN
207! ---             No contribution from "outside" cavity source, so
208! ---             set emission rate for "outside" source to zero.
209                  QC(2) = 0.0                                           !   2314
210                  SZC(2) = SZCAV0
211                  SYC(2) = SYCAV0
212                  SZC(3) = SZCAV0
213                  SYC(3) = SYCAV0
214                  N2 = 3
215               ELSEIF ( MODE.EQ.1 ) THEN
216! ---             No contribution from "inside" cavity source, so
217! ---             reset n2=2
218                  CALL WAKE_XSIG(XR,HC(2),0.0,LDB,DUMZ,DUMY,SZC(2),     &
219     &                           SYC(2))
220                  N2 = 2
221               ELSE
222! ---             Both cavity sources are used
223                  SZC(2) = SZCAV0                                       !   2924
224                  SYC(2) = SYCAV0
225                  SZC(3) = SZCAV0
226                  SYC(3) = SYCAV0
227                  IF ( XR.GE.0.0 ) CALL WAKE_XSIG(XR,HC(2),0.0,.TRUE.,  &
228     &                 DUMZ,DUMY,SZC(2),SYC(2))
229               ENDIF
230            ENDIF
231         ENDIF
232      ENDIF
233
234! --- Final check: receptor upwind of primary source, or all mass in cav
235! --- Do not allow n1=1 (primary source contribution)
236      IF ( N1.EQ.1 .AND. (XR.LE.0.0 .OR. FQCAV.EQ.1.0) ) N1 = 2         ! 421752
237
238      CONTINUE
239      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