1{-# OPTIONS_GHC -w #-}
2{-# OPTIONS -XMagicHash -XBangPatterns -XTypeSynonymInstances -XFlexibleInstances -cpp #-}
3#if __GLASGOW_HASKELL__ >= 710
4{-# OPTIONS_GHC -XPartialTypeSignatures #-}
5#endif
6{-# LANGUAGE ViewPatterns #-}
7{-# LANGUAGE TypeFamilies #-}
8{-# LANGUAGE LambdaCase #-}
9{-# LANGUAGE RankNTypes #-}
10{-# LANGUAGE GADTs #-}
11{-# LANGUAGE ScopedTypeVariables #-}
12
13-- | This module provides the generated Happy parser for Haskell. It exports
14-- a number of parsers which may be used in any library that uses the GHC API.
15-- A common usage pattern is to initialize the parser state with a given string
16-- and then parse that string:
17--
18-- @
19--     runParser :: DynFlags -> String -> P a -> ParseResult a
20--     runParser flags str parser = unP parser parseState
21--     where
22--       filename = "\<interactive\>"
23--       location = mkRealSrcLoc (mkFastString filename) 1 1
24--       buffer = stringToStringBuffer str
25--       parseState = mkPState flags buffer location
26-- @
27module Parser (parseModule, parseSignature, parseImport, parseStatement, parseBackpack,
28               parseDeclaration, parseExpression, parsePattern,
29               parseTypeSignature,
30               parseStmt, parseIdentifier,
31               parseType, parseHeader) where
32
33-- base
34import Control.Monad    ( unless, liftM, when, (<=<) )
35import GHC.Exts
36import Data.Char
37import Data.Maybe       ( maybeToList )
38import Control.Monad    ( mplus )
39import Control.Applicative ((<$))
40import qualified Prelude -- for happy-generated code
41
42-- compiler/hsSyn
43import GHC.Hs
44
45-- compiler/main
46import DriverPhases     ( HscSource(..) )
47import HscTypes         ( IsBootInterface, WarningTxt(..) )
48import DynFlags
49import BkpSyn
50import PackageConfig
51
52-- compiler/utils
53import OrdList
54import BooleanFormula   ( BooleanFormula(..), LBooleanFormula(..), mkTrue )
55import FastString
56import Maybes           ( isJust, orElse )
57import Outputable
58
59-- compiler/basicTypes
60import RdrName
61import OccName          ( varName, dataName, tcClsName, tvName, startsWithUnderscore )
62import DataCon          ( DataCon, dataConName )
63import SrcLoc
64import Module
65import BasicTypes
66
67-- compiler/types
68import Type             ( funTyCon )
69import Class            ( FunDep )
70
71-- compiler/parser
72import RdrHsSyn
73import Lexer
74import HaddockUtils
75import ApiAnnotation
76
77-- compiler/typecheck
78import TcEvidence       ( emptyTcEvBinds )
79
80-- compiler/prelude
81import ForeignCall
82import TysPrim          ( eqPrimTyCon )
83import TysWiredIn       ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nilDataCon,
84                          unboxedUnitTyCon, unboxedUnitDataCon,
85                          listTyCon_RDR, consDataCon_RDR, eqTyCon_RDR )
86
87-- compiler/utils
88import Util             ( looksLikePackageName, fstOf3, sndOf3, thdOf3 )
89import GhcPrelude
90import qualified Data.Array as Happy_Data_Array
91import qualified Data.Bits as Bits
92import qualified GHC.Exts as Happy_GHC_Exts
93import Control.Applicative(Applicative(..))
94import Control.Monad (ap)
95
96-- parser produced by Happy Version 1.19.12
97
98newtype HappyAbsSyn  = HappyAbsSyn HappyAny
99#if __GLASGOW_HASKELL__ >= 607
100type HappyAny = Happy_GHC_Exts.Any
101#else
102type HappyAny = forall a . a
103#endif
104newtype HappyWrap16 = HappyWrap16 (Located RdrName)
105happyIn16 :: (Located RdrName) -> (HappyAbsSyn )
106happyIn16 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap16 x)
107{-# INLINE happyIn16 #-}
108happyOut16 :: (HappyAbsSyn ) -> HappyWrap16
109happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
110{-# INLINE happyOut16 #-}
111newtype HappyWrap17 = HappyWrap17 ([LHsUnit PackageName])
112happyIn17 :: ([LHsUnit PackageName]) -> (HappyAbsSyn )
113happyIn17 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap17 x)
114{-# INLINE happyIn17 #-}
115happyOut17 :: (HappyAbsSyn ) -> HappyWrap17
116happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
117{-# INLINE happyOut17 #-}
118newtype HappyWrap18 = HappyWrap18 (OrdList (LHsUnit PackageName))
119happyIn18 :: (OrdList (LHsUnit PackageName)) -> (HappyAbsSyn )
120happyIn18 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap18 x)
121{-# INLINE happyIn18 #-}
122happyOut18 :: (HappyAbsSyn ) -> HappyWrap18
123happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
124{-# INLINE happyOut18 #-}
125newtype HappyWrap19 = HappyWrap19 (LHsUnit PackageName)
126happyIn19 :: (LHsUnit PackageName) -> (HappyAbsSyn )
127happyIn19 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap19 x)
128{-# INLINE happyIn19 #-}
129happyOut19 :: (HappyAbsSyn ) -> HappyWrap19
130happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
131{-# INLINE happyOut19 #-}
132newtype HappyWrap20 = HappyWrap20 (LHsUnitId PackageName)
133happyIn20 :: (LHsUnitId PackageName) -> (HappyAbsSyn )
134happyIn20 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap20 x)
135{-# INLINE happyIn20 #-}
136happyOut20 :: (HappyAbsSyn ) -> HappyWrap20
137happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
138{-# INLINE happyOut20 #-}
139newtype HappyWrap21 = HappyWrap21 (OrdList (LHsModuleSubst PackageName))
140happyIn21 :: (OrdList (LHsModuleSubst PackageName)) -> (HappyAbsSyn )
141happyIn21 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap21 x)
142{-# INLINE happyIn21 #-}
143happyOut21 :: (HappyAbsSyn ) -> HappyWrap21
144happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
145{-# INLINE happyOut21 #-}
146newtype HappyWrap22 = HappyWrap22 (LHsModuleSubst PackageName)
147happyIn22 :: (LHsModuleSubst PackageName) -> (HappyAbsSyn )
148happyIn22 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap22 x)
149{-# INLINE happyIn22 #-}
150happyOut22 :: (HappyAbsSyn ) -> HappyWrap22
151happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
152{-# INLINE happyOut22 #-}
153newtype HappyWrap23 = HappyWrap23 (LHsModuleId PackageName)
154happyIn23 :: (LHsModuleId PackageName) -> (HappyAbsSyn )
155happyIn23 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap23 x)
156{-# INLINE happyIn23 #-}
157happyOut23 :: (HappyAbsSyn ) -> HappyWrap23
158happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
159{-# INLINE happyOut23 #-}
160newtype HappyWrap24 = HappyWrap24 (Located PackageName)
161happyIn24 :: (Located PackageName) -> (HappyAbsSyn )
162happyIn24 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap24 x)
163{-# INLINE happyIn24 #-}
164happyOut24 :: (HappyAbsSyn ) -> HappyWrap24
165happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
166{-# INLINE happyOut24 #-}
167newtype HappyWrap25 = HappyWrap25 (Located FastString)
168happyIn25 :: (Located FastString) -> (HappyAbsSyn )
169happyIn25 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap25 x)
170{-# INLINE happyIn25 #-}
171happyOut25 :: (HappyAbsSyn ) -> HappyWrap25
172happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
173{-# INLINE happyOut25 #-}
174newtype HappyWrap26 = HappyWrap26 (Located FastString)
175happyIn26 :: (Located FastString) -> (HappyAbsSyn )
176happyIn26 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap26 x)
177{-# INLINE happyIn26 #-}
178happyOut26 :: (HappyAbsSyn ) -> HappyWrap26
179happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
180{-# INLINE happyOut26 #-}
181newtype HappyWrap27 = HappyWrap27 (Maybe [LRenaming])
182happyIn27 :: (Maybe [LRenaming]) -> (HappyAbsSyn )
183happyIn27 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap27 x)
184{-# INLINE happyIn27 #-}
185happyOut27 :: (HappyAbsSyn ) -> HappyWrap27
186happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x
187{-# INLINE happyOut27 #-}
188newtype HappyWrap28 = HappyWrap28 (OrdList LRenaming)
189happyIn28 :: (OrdList LRenaming) -> (HappyAbsSyn )
190happyIn28 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap28 x)
191{-# INLINE happyIn28 #-}
192happyOut28 :: (HappyAbsSyn ) -> HappyWrap28
193happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x
194{-# INLINE happyOut28 #-}
195newtype HappyWrap29 = HappyWrap29 (LRenaming)
196happyIn29 :: (LRenaming) -> (HappyAbsSyn )
197happyIn29 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap29 x)
198{-# INLINE happyIn29 #-}
199happyOut29 :: (HappyAbsSyn ) -> HappyWrap29
200happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x
201{-# INLINE happyOut29 #-}
202newtype HappyWrap30 = HappyWrap30 (OrdList (LHsUnitDecl PackageName))
203happyIn30 :: (OrdList (LHsUnitDecl PackageName)) -> (HappyAbsSyn )
204happyIn30 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap30 x)
205{-# INLINE happyIn30 #-}
206happyOut30 :: (HappyAbsSyn ) -> HappyWrap30
207happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x
208{-# INLINE happyOut30 #-}
209newtype HappyWrap31 = HappyWrap31 (OrdList (LHsUnitDecl PackageName))
210happyIn31 :: (OrdList (LHsUnitDecl PackageName)) -> (HappyAbsSyn )
211happyIn31 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap31 x)
212{-# INLINE happyIn31 #-}
213happyOut31 :: (HappyAbsSyn ) -> HappyWrap31
214happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x
215{-# INLINE happyOut31 #-}
216newtype HappyWrap32 = HappyWrap32 (LHsUnitDecl PackageName)
217happyIn32 :: (LHsUnitDecl PackageName) -> (HappyAbsSyn )
218happyIn32 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap32 x)
219{-# INLINE happyIn32 #-}
220happyOut32 :: (HappyAbsSyn ) -> HappyWrap32
221happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x
222{-# INLINE happyOut32 #-}
223newtype HappyWrap33 = HappyWrap33 (Located (HsModule GhcPs))
224happyIn33 :: (Located (HsModule GhcPs)) -> (HappyAbsSyn )
225happyIn33 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap33 x)
226{-# INLINE happyIn33 #-}
227happyOut33 :: (HappyAbsSyn ) -> HappyWrap33
228happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x
229{-# INLINE happyOut33 #-}
230newtype HappyWrap34 = HappyWrap34 (Located (HsModule GhcPs))
231happyIn34 :: (Located (HsModule GhcPs)) -> (HappyAbsSyn )
232happyIn34 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap34 x)
233{-# INLINE happyIn34 #-}
234happyOut34 :: (HappyAbsSyn ) -> HappyWrap34
235happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x
236{-# INLINE happyOut34 #-}
237newtype HappyWrap35 = HappyWrap35 (Maybe LHsDocString)
238happyIn35 :: (Maybe LHsDocString) -> (HappyAbsSyn )
239happyIn35 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap35 x)
240{-# INLINE happyIn35 #-}
241happyOut35 :: (HappyAbsSyn ) -> HappyWrap35
242happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x
243{-# INLINE happyOut35 #-}
244newtype HappyWrap36 = HappyWrap36 (())
245happyIn36 :: (()) -> (HappyAbsSyn )
246happyIn36 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap36 x)
247{-# INLINE happyIn36 #-}
248happyOut36 :: (HappyAbsSyn ) -> HappyWrap36
249happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x
250{-# INLINE happyOut36 #-}
251newtype HappyWrap37 = HappyWrap37 (())
252happyIn37 :: (()) -> (HappyAbsSyn )
253happyIn37 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap37 x)
254{-# INLINE happyIn37 #-}
255happyOut37 :: (HappyAbsSyn ) -> HappyWrap37
256happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x
257{-# INLINE happyOut37 #-}
258newtype HappyWrap38 = HappyWrap38 (Maybe (Located WarningTxt))
259happyIn38 :: (Maybe (Located WarningTxt)) -> (HappyAbsSyn )
260happyIn38 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap38 x)
261{-# INLINE happyIn38 #-}
262happyOut38 :: (HappyAbsSyn ) -> HappyWrap38
263happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x
264{-# INLINE happyOut38 #-}
265newtype HappyWrap39 = HappyWrap39 (([AddAnn]
266             ,([LImportDecl GhcPs], [LHsDecl GhcPs])))
267happyIn39 :: (([AddAnn]
268             ,([LImportDecl GhcPs], [LHsDecl GhcPs]))) -> (HappyAbsSyn )
269happyIn39 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap39 x)
270{-# INLINE happyIn39 #-}
271happyOut39 :: (HappyAbsSyn ) -> HappyWrap39
272happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x
273{-# INLINE happyOut39 #-}
274newtype HappyWrap40 = HappyWrap40 (([AddAnn]
275             ,([LImportDecl GhcPs], [LHsDecl GhcPs])))
276happyIn40 :: (([AddAnn]
277             ,([LImportDecl GhcPs], [LHsDecl GhcPs]))) -> (HappyAbsSyn )
278happyIn40 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap40 x)
279{-# INLINE happyIn40 #-}
280happyOut40 :: (HappyAbsSyn ) -> HappyWrap40
281happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x
282{-# INLINE happyOut40 #-}
283newtype HappyWrap41 = HappyWrap41 (([AddAnn]
284             ,([LImportDecl GhcPs], [LHsDecl GhcPs])))
285happyIn41 :: (([AddAnn]
286             ,([LImportDecl GhcPs], [LHsDecl GhcPs]))) -> (HappyAbsSyn )
287happyIn41 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap41 x)
288{-# INLINE happyIn41 #-}
289happyOut41 :: (HappyAbsSyn ) -> HappyWrap41
290happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x
291{-# INLINE happyOut41 #-}
292newtype HappyWrap42 = HappyWrap42 (([LImportDecl GhcPs], [LHsDecl GhcPs]))
293happyIn42 :: (([LImportDecl GhcPs], [LHsDecl GhcPs])) -> (HappyAbsSyn )
294happyIn42 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap42 x)
295{-# INLINE happyIn42 #-}
296happyOut42 :: (HappyAbsSyn ) -> HappyWrap42
297happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x
298{-# INLINE happyOut42 #-}
299newtype HappyWrap43 = HappyWrap43 (Located (HsModule GhcPs))
300happyIn43 :: (Located (HsModule GhcPs)) -> (HappyAbsSyn )
301happyIn43 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap43 x)
302{-# INLINE happyIn43 #-}
303happyOut43 :: (HappyAbsSyn ) -> HappyWrap43
304happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x
305{-# INLINE happyOut43 #-}
306newtype HappyWrap44 = HappyWrap44 ([LImportDecl GhcPs])
307happyIn44 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
308happyIn44 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap44 x)
309{-# INLINE happyIn44 #-}
310happyOut44 :: (HappyAbsSyn ) -> HappyWrap44
311happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x
312{-# INLINE happyOut44 #-}
313newtype HappyWrap45 = HappyWrap45 ([LImportDecl GhcPs])
314happyIn45 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
315happyIn45 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap45 x)
316{-# INLINE happyIn45 #-}
317happyOut45 :: (HappyAbsSyn ) -> HappyWrap45
318happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x
319{-# INLINE happyOut45 #-}
320newtype HappyWrap46 = HappyWrap46 ([LImportDecl GhcPs])
321happyIn46 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
322happyIn46 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap46 x)
323{-# INLINE happyIn46 #-}
324happyOut46 :: (HappyAbsSyn ) -> HappyWrap46
325happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x
326{-# INLINE happyOut46 #-}
327newtype HappyWrap47 = HappyWrap47 ([LImportDecl GhcPs])
328happyIn47 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
329happyIn47 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap47 x)
330{-# INLINE happyIn47 #-}
331happyOut47 :: (HappyAbsSyn ) -> HappyWrap47
332happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x
333{-# INLINE happyOut47 #-}
334newtype HappyWrap48 = HappyWrap48 ((Maybe (Located [LIE GhcPs])))
335happyIn48 :: ((Maybe (Located [LIE GhcPs]))) -> (HappyAbsSyn )
336happyIn48 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap48 x)
337{-# INLINE happyIn48 #-}
338happyOut48 :: (HappyAbsSyn ) -> HappyWrap48
339happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x
340{-# INLINE happyOut48 #-}
341newtype HappyWrap49 = HappyWrap49 (OrdList (LIE GhcPs))
342happyIn49 :: (OrdList (LIE GhcPs)) -> (HappyAbsSyn )
343happyIn49 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap49 x)
344{-# INLINE happyIn49 #-}
345happyOut49 :: (HappyAbsSyn ) -> HappyWrap49
346happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x
347{-# INLINE happyOut49 #-}
348newtype HappyWrap50 = HappyWrap50 (OrdList (LIE GhcPs))
349happyIn50 :: (OrdList (LIE GhcPs)) -> (HappyAbsSyn )
350happyIn50 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap50 x)
351{-# INLINE happyIn50 #-}
352happyOut50 :: (HappyAbsSyn ) -> HappyWrap50
353happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x
354{-# INLINE happyOut50 #-}
355newtype HappyWrap51 = HappyWrap51 (OrdList (LIE GhcPs))
356happyIn51 :: (OrdList (LIE GhcPs)) -> (HappyAbsSyn )
357happyIn51 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap51 x)
358{-# INLINE happyIn51 #-}
359happyOut51 :: (HappyAbsSyn ) -> HappyWrap51
360happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x
361{-# INLINE happyOut51 #-}
362newtype HappyWrap52 = HappyWrap52 (OrdList (LIE GhcPs))
363happyIn52 :: (OrdList (LIE GhcPs)) -> (HappyAbsSyn )
364happyIn52 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap52 x)
365{-# INLINE happyIn52 #-}
366happyOut52 :: (HappyAbsSyn ) -> HappyWrap52
367happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x
368{-# INLINE happyOut52 #-}
369newtype HappyWrap53 = HappyWrap53 (OrdList (LIE GhcPs))
370happyIn53 :: (OrdList (LIE GhcPs)) -> (HappyAbsSyn )
371happyIn53 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap53 x)
372{-# INLINE happyIn53 #-}
373happyOut53 :: (HappyAbsSyn ) -> HappyWrap53
374happyOut53 x = Happy_GHC_Exts.unsafeCoerce# x
375{-# INLINE happyOut53 #-}
376newtype HappyWrap54 = HappyWrap54 (Located ([AddAnn],ImpExpSubSpec))
377happyIn54 :: (Located ([AddAnn],ImpExpSubSpec)) -> (HappyAbsSyn )
378happyIn54 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap54 x)
379{-# INLINE happyIn54 #-}
380happyOut54 :: (HappyAbsSyn ) -> HappyWrap54
381happyOut54 x = Happy_GHC_Exts.unsafeCoerce# x
382{-# INLINE happyOut54 #-}
383newtype HappyWrap55 = HappyWrap55 (([AddAnn], [Located ImpExpQcSpec]))
384happyIn55 :: (([AddAnn], [Located ImpExpQcSpec])) -> (HappyAbsSyn )
385happyIn55 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap55 x)
386{-# INLINE happyIn55 #-}
387happyOut55 :: (HappyAbsSyn ) -> HappyWrap55
388happyOut55 x = Happy_GHC_Exts.unsafeCoerce# x
389{-# INLINE happyOut55 #-}
390newtype HappyWrap56 = HappyWrap56 (([AddAnn], [Located ImpExpQcSpec]))
391happyIn56 :: (([AddAnn], [Located ImpExpQcSpec])) -> (HappyAbsSyn )
392happyIn56 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap56 x)
393{-# INLINE happyIn56 #-}
394happyOut56 :: (HappyAbsSyn ) -> HappyWrap56
395happyOut56 x = Happy_GHC_Exts.unsafeCoerce# x
396{-# INLINE happyOut56 #-}
397newtype HappyWrap57 = HappyWrap57 (Located ([AddAnn], Located ImpExpQcSpec))
398happyIn57 :: (Located ([AddAnn], Located ImpExpQcSpec)) -> (HappyAbsSyn )
399happyIn57 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap57 x)
400{-# INLINE happyIn57 #-}
401happyOut57 :: (HappyAbsSyn ) -> HappyWrap57
402happyOut57 x = Happy_GHC_Exts.unsafeCoerce# x
403{-# INLINE happyOut57 #-}
404newtype HappyWrap58 = HappyWrap58 (Located ImpExpQcSpec)
405happyIn58 :: (Located ImpExpQcSpec) -> (HappyAbsSyn )
406happyIn58 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap58 x)
407{-# INLINE happyIn58 #-}
408happyOut58 :: (HappyAbsSyn ) -> HappyWrap58
409happyOut58 x = Happy_GHC_Exts.unsafeCoerce# x
410{-# INLINE happyOut58 #-}
411newtype HappyWrap59 = HappyWrap59 (Located RdrName)
412happyIn59 :: (Located RdrName) -> (HappyAbsSyn )
413happyIn59 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap59 x)
414{-# INLINE happyIn59 #-}
415happyOut59 :: (HappyAbsSyn ) -> HappyWrap59
416happyOut59 x = Happy_GHC_Exts.unsafeCoerce# x
417{-# INLINE happyOut59 #-}
418newtype HappyWrap60 = HappyWrap60 ([AddAnn])
419happyIn60 :: ([AddAnn]) -> (HappyAbsSyn )
420happyIn60 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap60 x)
421{-# INLINE happyIn60 #-}
422happyOut60 :: (HappyAbsSyn ) -> HappyWrap60
423happyOut60 x = Happy_GHC_Exts.unsafeCoerce# x
424{-# INLINE happyOut60 #-}
425newtype HappyWrap61 = HappyWrap61 ([AddAnn])
426happyIn61 :: ([AddAnn]) -> (HappyAbsSyn )
427happyIn61 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap61 x)
428{-# INLINE happyIn61 #-}
429happyOut61 :: (HappyAbsSyn ) -> HappyWrap61
430happyOut61 x = Happy_GHC_Exts.unsafeCoerce# x
431{-# INLINE happyOut61 #-}
432newtype HappyWrap62 = HappyWrap62 ([LImportDecl GhcPs])
433happyIn62 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
434happyIn62 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap62 x)
435{-# INLINE happyIn62 #-}
436happyOut62 :: (HappyAbsSyn ) -> HappyWrap62
437happyOut62 x = Happy_GHC_Exts.unsafeCoerce# x
438{-# INLINE happyOut62 #-}
439newtype HappyWrap63 = HappyWrap63 ([LImportDecl GhcPs])
440happyIn63 :: ([LImportDecl GhcPs]) -> (HappyAbsSyn )
441happyIn63 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap63 x)
442{-# INLINE happyIn63 #-}
443happyOut63 :: (HappyAbsSyn ) -> HappyWrap63
444happyOut63 x = Happy_GHC_Exts.unsafeCoerce# x
445{-# INLINE happyOut63 #-}
446newtype HappyWrap64 = HappyWrap64 (LImportDecl GhcPs)
447happyIn64 :: (LImportDecl GhcPs) -> (HappyAbsSyn )
448happyIn64 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap64 x)
449{-# INLINE happyIn64 #-}
450happyOut64 :: (HappyAbsSyn ) -> HappyWrap64
451happyOut64 x = Happy_GHC_Exts.unsafeCoerce# x
452{-# INLINE happyOut64 #-}
453newtype HappyWrap65 = HappyWrap65 ((([AddAnn],SourceText),IsBootInterface))
454happyIn65 :: ((([AddAnn],SourceText),IsBootInterface)) -> (HappyAbsSyn )
455happyIn65 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap65 x)
456{-# INLINE happyIn65 #-}
457happyOut65 :: (HappyAbsSyn ) -> HappyWrap65
458happyOut65 x = Happy_GHC_Exts.unsafeCoerce# x
459{-# INLINE happyOut65 #-}
460newtype HappyWrap66 = HappyWrap66 (([AddAnn],Bool))
461happyIn66 :: (([AddAnn],Bool)) -> (HappyAbsSyn )
462happyIn66 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap66 x)
463{-# INLINE happyIn66 #-}
464happyOut66 :: (HappyAbsSyn ) -> HappyWrap66
465happyOut66 x = Happy_GHC_Exts.unsafeCoerce# x
466{-# INLINE happyOut66 #-}
467newtype HappyWrap67 = HappyWrap67 (([AddAnn],Maybe StringLiteral))
468happyIn67 :: (([AddAnn],Maybe StringLiteral)) -> (HappyAbsSyn )
469happyIn67 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap67 x)
470{-# INLINE happyIn67 #-}
471happyOut67 :: (HappyAbsSyn ) -> HappyWrap67
472happyOut67 x = Happy_GHC_Exts.unsafeCoerce# x
473{-# INLINE happyOut67 #-}
474newtype HappyWrap68 = HappyWrap68 (Located (Maybe (Located Token)))
475happyIn68 :: (Located (Maybe (Located Token))) -> (HappyAbsSyn )
476happyIn68 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap68 x)
477{-# INLINE happyIn68 #-}
478happyOut68 :: (HappyAbsSyn ) -> HappyWrap68
479happyOut68 x = Happy_GHC_Exts.unsafeCoerce# x
480{-# INLINE happyOut68 #-}
481newtype HappyWrap69 = HappyWrap69 (([AddAnn],Located (Maybe (Located ModuleName))))
482happyIn69 :: (([AddAnn],Located (Maybe (Located ModuleName)))) -> (HappyAbsSyn )
483happyIn69 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap69 x)
484{-# INLINE happyIn69 #-}
485happyOut69 :: (HappyAbsSyn ) -> HappyWrap69
486happyOut69 x = Happy_GHC_Exts.unsafeCoerce# x
487{-# INLINE happyOut69 #-}
488newtype HappyWrap70 = HappyWrap70 (Located (Maybe (Bool, Located [LIE GhcPs])))
489happyIn70 :: (Located (Maybe (Bool, Located [LIE GhcPs]))) -> (HappyAbsSyn )
490happyIn70 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap70 x)
491{-# INLINE happyIn70 #-}
492happyOut70 :: (HappyAbsSyn ) -> HappyWrap70
493happyOut70 x = Happy_GHC_Exts.unsafeCoerce# x
494{-# INLINE happyOut70 #-}
495newtype HappyWrap71 = HappyWrap71 (Located (Bool, Located [LIE GhcPs]))
496happyIn71 :: (Located (Bool, Located [LIE GhcPs])) -> (HappyAbsSyn )
497happyIn71 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap71 x)
498{-# INLINE happyIn71 #-}
499happyOut71 :: (HappyAbsSyn ) -> HappyWrap71
500happyOut71 x = Happy_GHC_Exts.unsafeCoerce# x
501{-# INLINE happyOut71 #-}
502newtype HappyWrap72 = HappyWrap72 (Located (SourceText,Int))
503happyIn72 :: (Located (SourceText,Int)) -> (HappyAbsSyn )
504happyIn72 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap72 x)
505{-# INLINE happyIn72 #-}
506happyOut72 :: (HappyAbsSyn ) -> HappyWrap72
507happyOut72 x = Happy_GHC_Exts.unsafeCoerce# x
508{-# INLINE happyOut72 #-}
509newtype HappyWrap73 = HappyWrap73 (Located FixityDirection)
510happyIn73 :: (Located FixityDirection) -> (HappyAbsSyn )
511happyIn73 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap73 x)
512{-# INLINE happyIn73 #-}
513happyOut73 :: (HappyAbsSyn ) -> HappyWrap73
514happyOut73 x = Happy_GHC_Exts.unsafeCoerce# x
515{-# INLINE happyOut73 #-}
516newtype HappyWrap74 = HappyWrap74 (Located (OrdList (Located RdrName)))
517happyIn74 :: (Located (OrdList (Located RdrName))) -> (HappyAbsSyn )
518happyIn74 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap74 x)
519{-# INLINE happyIn74 #-}
520happyOut74 :: (HappyAbsSyn ) -> HappyWrap74
521happyOut74 x = Happy_GHC_Exts.unsafeCoerce# x
522{-# INLINE happyOut74 #-}
523newtype HappyWrap75 = HappyWrap75 (OrdList (LHsDecl GhcPs))
524happyIn75 :: (OrdList (LHsDecl GhcPs)) -> (HappyAbsSyn )
525happyIn75 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap75 x)
526{-# INLINE happyIn75 #-}
527happyOut75 :: (HappyAbsSyn ) -> HappyWrap75
528happyOut75 x = Happy_GHC_Exts.unsafeCoerce# x
529{-# INLINE happyOut75 #-}
530newtype HappyWrap76 = HappyWrap76 (OrdList (LHsDecl GhcPs))
531happyIn76 :: (OrdList (LHsDecl GhcPs)) -> (HappyAbsSyn )
532happyIn76 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap76 x)
533{-# INLINE happyIn76 #-}
534happyOut76 :: (HappyAbsSyn ) -> HappyWrap76
535happyOut76 x = Happy_GHC_Exts.unsafeCoerce# x
536{-# INLINE happyOut76 #-}
537newtype HappyWrap77 = HappyWrap77 (LHsDecl GhcPs)
538happyIn77 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
539happyIn77 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap77 x)
540{-# INLINE happyIn77 #-}
541happyOut77 :: (HappyAbsSyn ) -> HappyWrap77
542happyOut77 x = Happy_GHC_Exts.unsafeCoerce# x
543{-# INLINE happyOut77 #-}
544newtype HappyWrap78 = HappyWrap78 (LTyClDecl GhcPs)
545happyIn78 :: (LTyClDecl GhcPs) -> (HappyAbsSyn )
546happyIn78 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap78 x)
547{-# INLINE happyIn78 #-}
548happyOut78 :: (HappyAbsSyn ) -> HappyWrap78
549happyOut78 x = Happy_GHC_Exts.unsafeCoerce# x
550{-# INLINE happyOut78 #-}
551newtype HappyWrap79 = HappyWrap79 (LTyClDecl GhcPs)
552happyIn79 :: (LTyClDecl GhcPs) -> (HappyAbsSyn )
553happyIn79 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap79 x)
554{-# INLINE happyIn79 #-}
555happyOut79 :: (HappyAbsSyn ) -> HappyWrap79
556happyOut79 x = Happy_GHC_Exts.unsafeCoerce# x
557{-# INLINE happyOut79 #-}
558newtype HappyWrap80 = HappyWrap80 (LStandaloneKindSig GhcPs)
559happyIn80 :: (LStandaloneKindSig GhcPs) -> (HappyAbsSyn )
560happyIn80 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap80 x)
561{-# INLINE happyIn80 #-}
562happyOut80 :: (HappyAbsSyn ) -> HappyWrap80
563happyOut80 x = Happy_GHC_Exts.unsafeCoerce# x
564{-# INLINE happyOut80 #-}
565newtype HappyWrap81 = HappyWrap81 (Located [Located RdrName])
566happyIn81 :: (Located [Located RdrName]) -> (HappyAbsSyn )
567happyIn81 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap81 x)
568{-# INLINE happyIn81 #-}
569happyOut81 :: (HappyAbsSyn ) -> HappyWrap81
570happyOut81 x = Happy_GHC_Exts.unsafeCoerce# x
571{-# INLINE happyOut81 #-}
572newtype HappyWrap82 = HappyWrap82 (LInstDecl GhcPs)
573happyIn82 :: (LInstDecl GhcPs) -> (HappyAbsSyn )
574happyIn82 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap82 x)
575{-# INLINE happyIn82 #-}
576happyOut82 :: (HappyAbsSyn ) -> HappyWrap82
577happyOut82 x = Happy_GHC_Exts.unsafeCoerce# x
578{-# INLINE happyOut82 #-}
579newtype HappyWrap83 = HappyWrap83 (Maybe (Located OverlapMode))
580happyIn83 :: (Maybe (Located OverlapMode)) -> (HappyAbsSyn )
581happyIn83 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap83 x)
582{-# INLINE happyIn83 #-}
583happyOut83 :: (HappyAbsSyn ) -> HappyWrap83
584happyOut83 x = Happy_GHC_Exts.unsafeCoerce# x
585{-# INLINE happyOut83 #-}
586newtype HappyWrap84 = HappyWrap84 (LDerivStrategy GhcPs)
587happyIn84 :: (LDerivStrategy GhcPs) -> (HappyAbsSyn )
588happyIn84 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap84 x)
589{-# INLINE happyIn84 #-}
590happyOut84 :: (HappyAbsSyn ) -> HappyWrap84
591happyOut84 x = Happy_GHC_Exts.unsafeCoerce# x
592{-# INLINE happyOut84 #-}
593newtype HappyWrap85 = HappyWrap85 (LDerivStrategy GhcPs)
594happyIn85 :: (LDerivStrategy GhcPs) -> (HappyAbsSyn )
595happyIn85 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap85 x)
596{-# INLINE happyIn85 #-}
597happyOut85 :: (HappyAbsSyn ) -> HappyWrap85
598happyOut85 x = Happy_GHC_Exts.unsafeCoerce# x
599{-# INLINE happyOut85 #-}
600newtype HappyWrap86 = HappyWrap86 (Maybe (LDerivStrategy GhcPs))
601happyIn86 :: (Maybe (LDerivStrategy GhcPs)) -> (HappyAbsSyn )
602happyIn86 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap86 x)
603{-# INLINE happyIn86 #-}
604happyOut86 :: (HappyAbsSyn ) -> HappyWrap86
605happyOut86 x = Happy_GHC_Exts.unsafeCoerce# x
606{-# INLINE happyOut86 #-}
607newtype HappyWrap87 = HappyWrap87 (Located ([AddAnn], Maybe (LInjectivityAnn GhcPs)))
608happyIn87 :: (Located ([AddAnn], Maybe (LInjectivityAnn GhcPs))) -> (HappyAbsSyn )
609happyIn87 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap87 x)
610{-# INLINE happyIn87 #-}
611happyOut87 :: (HappyAbsSyn ) -> HappyWrap87
612happyOut87 x = Happy_GHC_Exts.unsafeCoerce# x
613{-# INLINE happyOut87 #-}
614newtype HappyWrap88 = HappyWrap88 (LInjectivityAnn GhcPs)
615happyIn88 :: (LInjectivityAnn GhcPs) -> (HappyAbsSyn )
616happyIn88 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap88 x)
617{-# INLINE happyIn88 #-}
618happyOut88 :: (HappyAbsSyn ) -> HappyWrap88
619happyOut88 x = Happy_GHC_Exts.unsafeCoerce# x
620{-# INLINE happyOut88 #-}
621newtype HappyWrap89 = HappyWrap89 (Located [Located RdrName])
622happyIn89 :: (Located [Located RdrName]) -> (HappyAbsSyn )
623happyIn89 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap89 x)
624{-# INLINE happyIn89 #-}
625happyOut89 :: (HappyAbsSyn ) -> HappyWrap89
626happyOut89 x = Happy_GHC_Exts.unsafeCoerce# x
627{-# INLINE happyOut89 #-}
628newtype HappyWrap90 = HappyWrap90 (Located ([AddAnn],FamilyInfo GhcPs))
629happyIn90 :: (Located ([AddAnn],FamilyInfo GhcPs)) -> (HappyAbsSyn )
630happyIn90 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap90 x)
631{-# INLINE happyIn90 #-}
632happyOut90 :: (HappyAbsSyn ) -> HappyWrap90
633happyOut90 x = Happy_GHC_Exts.unsafeCoerce# x
634{-# INLINE happyOut90 #-}
635newtype HappyWrap91 = HappyWrap91 (Located ([AddAnn],Maybe [LTyFamInstEqn GhcPs]))
636happyIn91 :: (Located ([AddAnn],Maybe [LTyFamInstEqn GhcPs])) -> (HappyAbsSyn )
637happyIn91 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap91 x)
638{-# INLINE happyIn91 #-}
639happyOut91 :: (HappyAbsSyn ) -> HappyWrap91
640happyOut91 x = Happy_GHC_Exts.unsafeCoerce# x
641{-# INLINE happyOut91 #-}
642newtype HappyWrap92 = HappyWrap92 (Located [LTyFamInstEqn GhcPs])
643happyIn92 :: (Located [LTyFamInstEqn GhcPs]) -> (HappyAbsSyn )
644happyIn92 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap92 x)
645{-# INLINE happyIn92 #-}
646happyOut92 :: (HappyAbsSyn ) -> HappyWrap92
647happyOut92 x = Happy_GHC_Exts.unsafeCoerce# x
648{-# INLINE happyOut92 #-}
649newtype HappyWrap93 = HappyWrap93 (Located ([AddAnn],TyFamInstEqn GhcPs))
650happyIn93 :: (Located ([AddAnn],TyFamInstEqn GhcPs)) -> (HappyAbsSyn )
651happyIn93 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap93 x)
652{-# INLINE happyIn93 #-}
653happyOut93 :: (HappyAbsSyn ) -> HappyWrap93
654happyOut93 x = Happy_GHC_Exts.unsafeCoerce# x
655{-# INLINE happyOut93 #-}
656newtype HappyWrap94 = HappyWrap94 (LHsDecl GhcPs)
657happyIn94 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
658happyIn94 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap94 x)
659{-# INLINE happyIn94 #-}
660happyOut94 :: (HappyAbsSyn ) -> HappyWrap94
661happyOut94 x = Happy_GHC_Exts.unsafeCoerce# x
662{-# INLINE happyOut94 #-}
663newtype HappyWrap95 = HappyWrap95 ([AddAnn])
664happyIn95 :: ([AddAnn]) -> (HappyAbsSyn )
665happyIn95 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap95 x)
666{-# INLINE happyIn95 #-}
667happyOut95 :: (HappyAbsSyn ) -> HappyWrap95
668happyOut95 x = Happy_GHC_Exts.unsafeCoerce# x
669{-# INLINE happyOut95 #-}
670newtype HappyWrap96 = HappyWrap96 ([AddAnn])
671happyIn96 :: ([AddAnn]) -> (HappyAbsSyn )
672happyIn96 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap96 x)
673{-# INLINE happyIn96 #-}
674happyOut96 :: (HappyAbsSyn ) -> HappyWrap96
675happyOut96 x = Happy_GHC_Exts.unsafeCoerce# x
676{-# INLINE happyOut96 #-}
677newtype HappyWrap97 = HappyWrap97 (LInstDecl GhcPs)
678happyIn97 :: (LInstDecl GhcPs) -> (HappyAbsSyn )
679happyIn97 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap97 x)
680{-# INLINE happyIn97 #-}
681happyOut97 :: (HappyAbsSyn ) -> HappyWrap97
682happyOut97 x = Happy_GHC_Exts.unsafeCoerce# x
683{-# INLINE happyOut97 #-}
684newtype HappyWrap98 = HappyWrap98 (Located (AddAnn, NewOrData))
685happyIn98 :: (Located (AddAnn, NewOrData)) -> (HappyAbsSyn )
686happyIn98 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap98 x)
687{-# INLINE happyIn98 #-}
688happyOut98 :: (HappyAbsSyn ) -> HappyWrap98
689happyOut98 x = Happy_GHC_Exts.unsafeCoerce# x
690{-# INLINE happyOut98 #-}
691newtype HappyWrap99 = HappyWrap99 (Located ([AddAnn], Maybe (LHsKind GhcPs)))
692happyIn99 :: (Located ([AddAnn], Maybe (LHsKind GhcPs))) -> (HappyAbsSyn )
693happyIn99 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap99 x)
694{-# INLINE happyIn99 #-}
695happyOut99 :: (HappyAbsSyn ) -> HappyWrap99
696happyOut99 x = Happy_GHC_Exts.unsafeCoerce# x
697{-# INLINE happyOut99 #-}
698newtype HappyWrap100 = HappyWrap100 (Located ([AddAnn], LFamilyResultSig GhcPs))
699happyIn100 :: (Located ([AddAnn], LFamilyResultSig GhcPs)) -> (HappyAbsSyn )
700happyIn100 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap100 x)
701{-# INLINE happyIn100 #-}
702happyOut100 :: (HappyAbsSyn ) -> HappyWrap100
703happyOut100 x = Happy_GHC_Exts.unsafeCoerce# x
704{-# INLINE happyOut100 #-}
705newtype HappyWrap101 = HappyWrap101 (Located ([AddAnn], LFamilyResultSig GhcPs))
706happyIn101 :: (Located ([AddAnn], LFamilyResultSig GhcPs)) -> (HappyAbsSyn )
707happyIn101 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap101 x)
708{-# INLINE happyIn101 #-}
709happyOut101 :: (HappyAbsSyn ) -> HappyWrap101
710happyOut101 x = Happy_GHC_Exts.unsafeCoerce# x
711{-# INLINE happyOut101 #-}
712newtype HappyWrap102 = HappyWrap102 (Located ([AddAnn], ( LFamilyResultSig GhcPs
713                                            , Maybe (LInjectivityAnn GhcPs))))
714happyIn102 :: (Located ([AddAnn], ( LFamilyResultSig GhcPs
715                                            , Maybe (LInjectivityAnn GhcPs)))) -> (HappyAbsSyn )
716happyIn102 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap102 x)
717{-# INLINE happyIn102 #-}
718happyOut102 :: (HappyAbsSyn ) -> HappyWrap102
719happyOut102 x = Happy_GHC_Exts.unsafeCoerce# x
720{-# INLINE happyOut102 #-}
721newtype HappyWrap103 = HappyWrap103 (Located (Maybe (LHsContext GhcPs), LHsType GhcPs))
722happyIn103 :: (Located (Maybe (LHsContext GhcPs), LHsType GhcPs)) -> (HappyAbsSyn )
723happyIn103 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap103 x)
724{-# INLINE happyIn103 #-}
725happyOut103 :: (HappyAbsSyn ) -> HappyWrap103
726happyOut103 x = Happy_GHC_Exts.unsafeCoerce# x
727{-# INLINE happyOut103 #-}
728newtype HappyWrap104 = HappyWrap104 (Located ([AddAnn],(Maybe (LHsContext GhcPs), Maybe [LHsTyVarBndr GhcPs], LHsType GhcPs)))
729happyIn104 :: (Located ([AddAnn],(Maybe (LHsContext GhcPs), Maybe [LHsTyVarBndr GhcPs], LHsType GhcPs))) -> (HappyAbsSyn )
730happyIn104 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap104 x)
731{-# INLINE happyIn104 #-}
732happyOut104 :: (HappyAbsSyn ) -> HappyWrap104
733happyOut104 x = Happy_GHC_Exts.unsafeCoerce# x
734{-# INLINE happyOut104 #-}
735newtype HappyWrap105 = HappyWrap105 (Maybe (Located CType))
736happyIn105 :: (Maybe (Located CType)) -> (HappyAbsSyn )
737happyIn105 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap105 x)
738{-# INLINE happyIn105 #-}
739happyOut105 :: (HappyAbsSyn ) -> HappyWrap105
740happyOut105 x = Happy_GHC_Exts.unsafeCoerce# x
741{-# INLINE happyOut105 #-}
742newtype HappyWrap106 = HappyWrap106 (LDerivDecl GhcPs)
743happyIn106 :: (LDerivDecl GhcPs) -> (HappyAbsSyn )
744happyIn106 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap106 x)
745{-# INLINE happyIn106 #-}
746happyOut106 :: (HappyAbsSyn ) -> HappyWrap106
747happyOut106 x = Happy_GHC_Exts.unsafeCoerce# x
748{-# INLINE happyOut106 #-}
749newtype HappyWrap107 = HappyWrap107 (LRoleAnnotDecl GhcPs)
750happyIn107 :: (LRoleAnnotDecl GhcPs) -> (HappyAbsSyn )
751happyIn107 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap107 x)
752{-# INLINE happyIn107 #-}
753happyOut107 :: (HappyAbsSyn ) -> HappyWrap107
754happyOut107 x = Happy_GHC_Exts.unsafeCoerce# x
755{-# INLINE happyOut107 #-}
756newtype HappyWrap108 = HappyWrap108 (Located [Located (Maybe FastString)])
757happyIn108 :: (Located [Located (Maybe FastString)]) -> (HappyAbsSyn )
758happyIn108 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap108 x)
759{-# INLINE happyIn108 #-}
760happyOut108 :: (HappyAbsSyn ) -> HappyWrap108
761happyOut108 x = Happy_GHC_Exts.unsafeCoerce# x
762{-# INLINE happyOut108 #-}
763newtype HappyWrap109 = HappyWrap109 (Located [Located (Maybe FastString)])
764happyIn109 :: (Located [Located (Maybe FastString)]) -> (HappyAbsSyn )
765happyIn109 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap109 x)
766{-# INLINE happyIn109 #-}
767happyOut109 :: (HappyAbsSyn ) -> HappyWrap109
768happyOut109 x = Happy_GHC_Exts.unsafeCoerce# x
769{-# INLINE happyOut109 #-}
770newtype HappyWrap110 = HappyWrap110 (Located (Maybe FastString))
771happyIn110 :: (Located (Maybe FastString)) -> (HappyAbsSyn )
772happyIn110 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap110 x)
773{-# INLINE happyIn110 #-}
774happyOut110 :: (HappyAbsSyn ) -> HappyWrap110
775happyOut110 x = Happy_GHC_Exts.unsafeCoerce# x
776{-# INLINE happyOut110 #-}
777newtype HappyWrap111 = HappyWrap111 (LHsDecl GhcPs)
778happyIn111 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
779happyIn111 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap111 x)
780{-# INLINE happyIn111 #-}
781happyOut111 :: (HappyAbsSyn ) -> HappyWrap111
782happyOut111 x = Happy_GHC_Exts.unsafeCoerce# x
783{-# INLINE happyOut111 #-}
784newtype HappyWrap112 = HappyWrap112 ((Located RdrName, HsPatSynDetails (Located RdrName), [AddAnn]))
785happyIn112 :: ((Located RdrName, HsPatSynDetails (Located RdrName), [AddAnn])) -> (HappyAbsSyn )
786happyIn112 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap112 x)
787{-# INLINE happyIn112 #-}
788happyOut112 :: (HappyAbsSyn ) -> HappyWrap112
789happyOut112 x = Happy_GHC_Exts.unsafeCoerce# x
790{-# INLINE happyOut112 #-}
791newtype HappyWrap113 = HappyWrap113 ([Located RdrName])
792happyIn113 :: ([Located RdrName]) -> (HappyAbsSyn )
793happyIn113 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap113 x)
794{-# INLINE happyIn113 #-}
795happyOut113 :: (HappyAbsSyn ) -> HappyWrap113
796happyOut113 x = Happy_GHC_Exts.unsafeCoerce# x
797{-# INLINE happyOut113 #-}
798newtype HappyWrap114 = HappyWrap114 ([RecordPatSynField (Located RdrName)])
799happyIn114 :: ([RecordPatSynField (Located RdrName)]) -> (HappyAbsSyn )
800happyIn114 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap114 x)
801{-# INLINE happyIn114 #-}
802happyOut114 :: (HappyAbsSyn ) -> HappyWrap114
803happyOut114 x = Happy_GHC_Exts.unsafeCoerce# x
804{-# INLINE happyOut114 #-}
805newtype HappyWrap115 = HappyWrap115 (Located ([AddAnn]
806                         , Located (OrdList (LHsDecl GhcPs))))
807happyIn115 :: (Located ([AddAnn]
808                         , Located (OrdList (LHsDecl GhcPs)))) -> (HappyAbsSyn )
809happyIn115 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap115 x)
810{-# INLINE happyIn115 #-}
811happyOut115 :: (HappyAbsSyn ) -> HappyWrap115
812happyOut115 x = Happy_GHC_Exts.unsafeCoerce# x
813{-# INLINE happyOut115 #-}
814newtype HappyWrap116 = HappyWrap116 (LSig GhcPs)
815happyIn116 :: (LSig GhcPs) -> (HappyAbsSyn )
816happyIn116 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap116 x)
817{-# INLINE happyIn116 #-}
818happyOut116 :: (HappyAbsSyn ) -> HappyWrap116
819happyOut116 x = Happy_GHC_Exts.unsafeCoerce# x
820{-# INLINE happyOut116 #-}
821newtype HappyWrap117 = HappyWrap117 (LHsDecl GhcPs)
822happyIn117 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
823happyIn117 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap117 x)
824{-# INLINE happyIn117 #-}
825happyOut117 :: (HappyAbsSyn ) -> HappyWrap117
826happyOut117 x = Happy_GHC_Exts.unsafeCoerce# x
827{-# INLINE happyOut117 #-}
828newtype HappyWrap118 = HappyWrap118 (Located ([AddAnn],OrdList (LHsDecl GhcPs)))
829happyIn118 :: (Located ([AddAnn],OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
830happyIn118 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap118 x)
831{-# INLINE happyIn118 #-}
832happyOut118 :: (HappyAbsSyn ) -> HappyWrap118
833happyOut118 x = Happy_GHC_Exts.unsafeCoerce# x
834{-# INLINE happyOut118 #-}
835newtype HappyWrap119 = HappyWrap119 (Located ([AddAnn]
836                     , OrdList (LHsDecl GhcPs)))
837happyIn119 :: (Located ([AddAnn]
838                     , OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
839happyIn119 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap119 x)
840{-# INLINE happyIn119 #-}
841happyOut119 :: (HappyAbsSyn ) -> HappyWrap119
842happyOut119 x = Happy_GHC_Exts.unsafeCoerce# x
843{-# INLINE happyOut119 #-}
844newtype HappyWrap120 = HappyWrap120 (Located ([AddAnn]
845                       ,(OrdList (LHsDecl GhcPs))))
846happyIn120 :: (Located ([AddAnn]
847                       ,(OrdList (LHsDecl GhcPs)))) -> (HappyAbsSyn )
848happyIn120 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap120 x)
849{-# INLINE happyIn120 #-}
850happyOut120 :: (HappyAbsSyn ) -> HappyWrap120
851happyOut120 x = Happy_GHC_Exts.unsafeCoerce# x
852{-# INLINE happyOut120 #-}
853newtype HappyWrap121 = HappyWrap121 (Located (OrdList (LHsDecl GhcPs)))
854happyIn121 :: (Located (OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
855happyIn121 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap121 x)
856{-# INLINE happyIn121 #-}
857happyOut121 :: (HappyAbsSyn ) -> HappyWrap121
858happyOut121 x = Happy_GHC_Exts.unsafeCoerce# x
859{-# INLINE happyOut121 #-}
860newtype HappyWrap122 = HappyWrap122 (Located ([AddAnn],OrdList (LHsDecl GhcPs)))
861happyIn122 :: (Located ([AddAnn],OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
862happyIn122 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap122 x)
863{-# INLINE happyIn122 #-}
864happyOut122 :: (HappyAbsSyn ) -> HappyWrap122
865happyOut122 x = Happy_GHC_Exts.unsafeCoerce# x
866{-# INLINE happyOut122 #-}
867newtype HappyWrap123 = HappyWrap123 (Located ([AddAnn]
868                     , OrdList (LHsDecl GhcPs)))
869happyIn123 :: (Located ([AddAnn]
870                     , OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
871happyIn123 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap123 x)
872{-# INLINE happyIn123 #-}
873happyOut123 :: (HappyAbsSyn ) -> HappyWrap123
874happyOut123 x = Happy_GHC_Exts.unsafeCoerce# x
875{-# INLINE happyOut123 #-}
876newtype HappyWrap124 = HappyWrap124 (Located ([AddAnn]
877                        , OrdList (LHsDecl GhcPs)))
878happyIn124 :: (Located ([AddAnn]
879                        , OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
880happyIn124 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap124 x)
881{-# INLINE happyIn124 #-}
882happyOut124 :: (HappyAbsSyn ) -> HappyWrap124
883happyOut124 x = Happy_GHC_Exts.unsafeCoerce# x
884{-# INLINE happyOut124 #-}
885newtype HappyWrap125 = HappyWrap125 (Located ([AddAnn],OrdList (LHsDecl GhcPs)))
886happyIn125 :: (Located ([AddAnn],OrdList (LHsDecl GhcPs))) -> (HappyAbsSyn )
887happyIn125 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap125 x)
888{-# INLINE happyIn125 #-}
889happyOut125 :: (HappyAbsSyn ) -> HappyWrap125
890happyOut125 x = Happy_GHC_Exts.unsafeCoerce# x
891{-# INLINE happyOut125 #-}
892newtype HappyWrap126 = HappyWrap126 (Located ([AddAnn],Located (OrdList (LHsDecl GhcPs))))
893happyIn126 :: (Located ([AddAnn],Located (OrdList (LHsDecl GhcPs)))) -> (HappyAbsSyn )
894happyIn126 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap126 x)
895{-# INLINE happyIn126 #-}
896happyOut126 :: (HappyAbsSyn ) -> HappyWrap126
897happyOut126 x = Happy_GHC_Exts.unsafeCoerce# x
898{-# INLINE happyOut126 #-}
899newtype HappyWrap127 = HappyWrap127 (Located ([AddAnn],Located (HsLocalBinds GhcPs)))
900happyIn127 :: (Located ([AddAnn],Located (HsLocalBinds GhcPs))) -> (HappyAbsSyn )
901happyIn127 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap127 x)
902{-# INLINE happyIn127 #-}
903happyOut127 :: (HappyAbsSyn ) -> HappyWrap127
904happyOut127 x = Happy_GHC_Exts.unsafeCoerce# x
905{-# INLINE happyOut127 #-}
906newtype HappyWrap128 = HappyWrap128 (Located ([AddAnn],Located (HsLocalBinds GhcPs)))
907happyIn128 :: (Located ([AddAnn],Located (HsLocalBinds GhcPs))) -> (HappyAbsSyn )
908happyIn128 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap128 x)
909{-# INLINE happyIn128 #-}
910happyOut128 :: (HappyAbsSyn ) -> HappyWrap128
911happyOut128 x = Happy_GHC_Exts.unsafeCoerce# x
912{-# INLINE happyOut128 #-}
913newtype HappyWrap129 = HappyWrap129 (OrdList (LRuleDecl GhcPs))
914happyIn129 :: (OrdList (LRuleDecl GhcPs)) -> (HappyAbsSyn )
915happyIn129 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap129 x)
916{-# INLINE happyIn129 #-}
917happyOut129 :: (HappyAbsSyn ) -> HappyWrap129
918happyOut129 x = Happy_GHC_Exts.unsafeCoerce# x
919{-# INLINE happyOut129 #-}
920newtype HappyWrap130 = HappyWrap130 (LRuleDecl GhcPs)
921happyIn130 :: (LRuleDecl GhcPs) -> (HappyAbsSyn )
922happyIn130 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap130 x)
923{-# INLINE happyIn130 #-}
924happyOut130 :: (HappyAbsSyn ) -> HappyWrap130
925happyOut130 x = Happy_GHC_Exts.unsafeCoerce# x
926{-# INLINE happyOut130 #-}
927newtype HappyWrap131 = HappyWrap131 (([AddAnn],Maybe Activation))
928happyIn131 :: (([AddAnn],Maybe Activation)) -> (HappyAbsSyn )
929happyIn131 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap131 x)
930{-# INLINE happyIn131 #-}
931happyOut131 :: (HappyAbsSyn ) -> HappyWrap131
932happyOut131 x = Happy_GHC_Exts.unsafeCoerce# x
933{-# INLINE happyOut131 #-}
934newtype HappyWrap132 = HappyWrap132 (([AddAnn]
935                              ,Activation))
936happyIn132 :: (([AddAnn]
937                              ,Activation)) -> (HappyAbsSyn )
938happyIn132 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap132 x)
939{-# INLINE happyIn132 #-}
940happyOut132 :: (HappyAbsSyn ) -> HappyWrap132
941happyOut132 x = Happy_GHC_Exts.unsafeCoerce# x
942{-# INLINE happyOut132 #-}
943newtype HappyWrap133 = HappyWrap133 (([AddAnn], Maybe [LHsTyVarBndr GhcPs], [LRuleBndr GhcPs]))
944happyIn133 :: (([AddAnn], Maybe [LHsTyVarBndr GhcPs], [LRuleBndr GhcPs])) -> (HappyAbsSyn )
945happyIn133 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap133 x)
946{-# INLINE happyIn133 #-}
947happyOut133 :: (HappyAbsSyn ) -> HappyWrap133
948happyOut133 x = Happy_GHC_Exts.unsafeCoerce# x
949{-# INLINE happyOut133 #-}
950newtype HappyWrap134 = HappyWrap134 ([LRuleTyTmVar])
951happyIn134 :: ([LRuleTyTmVar]) -> (HappyAbsSyn )
952happyIn134 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap134 x)
953{-# INLINE happyIn134 #-}
954happyOut134 :: (HappyAbsSyn ) -> HappyWrap134
955happyOut134 x = Happy_GHC_Exts.unsafeCoerce# x
956{-# INLINE happyOut134 #-}
957newtype HappyWrap135 = HappyWrap135 (LRuleTyTmVar)
958happyIn135 :: (LRuleTyTmVar) -> (HappyAbsSyn )
959happyIn135 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap135 x)
960{-# INLINE happyIn135 #-}
961happyOut135 :: (HappyAbsSyn ) -> HappyWrap135
962happyOut135 x = Happy_GHC_Exts.unsafeCoerce# x
963{-# INLINE happyOut135 #-}
964newtype HappyWrap136 = HappyWrap136 (OrdList (LWarnDecl GhcPs))
965happyIn136 :: (OrdList (LWarnDecl GhcPs)) -> (HappyAbsSyn )
966happyIn136 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap136 x)
967{-# INLINE happyIn136 #-}
968happyOut136 :: (HappyAbsSyn ) -> HappyWrap136
969happyOut136 x = Happy_GHC_Exts.unsafeCoerce# x
970{-# INLINE happyOut136 #-}
971newtype HappyWrap137 = HappyWrap137 (OrdList (LWarnDecl GhcPs))
972happyIn137 :: (OrdList (LWarnDecl GhcPs)) -> (HappyAbsSyn )
973happyIn137 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap137 x)
974{-# INLINE happyIn137 #-}
975happyOut137 :: (HappyAbsSyn ) -> HappyWrap137
976happyOut137 x = Happy_GHC_Exts.unsafeCoerce# x
977{-# INLINE happyOut137 #-}
978newtype HappyWrap138 = HappyWrap138 (OrdList (LWarnDecl GhcPs))
979happyIn138 :: (OrdList (LWarnDecl GhcPs)) -> (HappyAbsSyn )
980happyIn138 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap138 x)
981{-# INLINE happyIn138 #-}
982happyOut138 :: (HappyAbsSyn ) -> HappyWrap138
983happyOut138 x = Happy_GHC_Exts.unsafeCoerce# x
984{-# INLINE happyOut138 #-}
985newtype HappyWrap139 = HappyWrap139 (OrdList (LWarnDecl GhcPs))
986happyIn139 :: (OrdList (LWarnDecl GhcPs)) -> (HappyAbsSyn )
987happyIn139 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap139 x)
988{-# INLINE happyIn139 #-}
989happyOut139 :: (HappyAbsSyn ) -> HappyWrap139
990happyOut139 x = Happy_GHC_Exts.unsafeCoerce# x
991{-# INLINE happyOut139 #-}
992newtype HappyWrap140 = HappyWrap140 (Located ([AddAnn],[Located StringLiteral]))
993happyIn140 :: (Located ([AddAnn],[Located StringLiteral])) -> (HappyAbsSyn )
994happyIn140 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap140 x)
995{-# INLINE happyIn140 #-}
996happyOut140 :: (HappyAbsSyn ) -> HappyWrap140
997happyOut140 x = Happy_GHC_Exts.unsafeCoerce# x
998{-# INLINE happyOut140 #-}
999newtype HappyWrap141 = HappyWrap141 (Located (OrdList (Located StringLiteral)))
1000happyIn141 :: (Located (OrdList (Located StringLiteral))) -> (HappyAbsSyn )
1001happyIn141 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap141 x)
1002{-# INLINE happyIn141 #-}
1003happyOut141 :: (HappyAbsSyn ) -> HappyWrap141
1004happyOut141 x = Happy_GHC_Exts.unsafeCoerce# x
1005{-# INLINE happyOut141 #-}
1006newtype HappyWrap142 = HappyWrap142 (LHsDecl GhcPs)
1007happyIn142 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
1008happyIn142 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap142 x)
1009{-# INLINE happyIn142 #-}
1010happyOut142 :: (HappyAbsSyn ) -> HappyWrap142
1011happyOut142 x = Happy_GHC_Exts.unsafeCoerce# x
1012{-# INLINE happyOut142 #-}
1013newtype HappyWrap143 = HappyWrap143 (Located ([AddAnn],HsDecl GhcPs))
1014happyIn143 :: (Located ([AddAnn],HsDecl GhcPs)) -> (HappyAbsSyn )
1015happyIn143 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap143 x)
1016{-# INLINE happyIn143 #-}
1017happyOut143 :: (HappyAbsSyn ) -> HappyWrap143
1018happyOut143 x = Happy_GHC_Exts.unsafeCoerce# x
1019{-# INLINE happyOut143 #-}
1020newtype HappyWrap144 = HappyWrap144 (Located CCallConv)
1021happyIn144 :: (Located CCallConv) -> (HappyAbsSyn )
1022happyIn144 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap144 x)
1023{-# INLINE happyIn144 #-}
1024happyOut144 :: (HappyAbsSyn ) -> HappyWrap144
1025happyOut144 x = Happy_GHC_Exts.unsafeCoerce# x
1026{-# INLINE happyOut144 #-}
1027newtype HappyWrap145 = HappyWrap145 (Located Safety)
1028happyIn145 :: (Located Safety) -> (HappyAbsSyn )
1029happyIn145 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap145 x)
1030{-# INLINE happyIn145 #-}
1031happyOut145 :: (HappyAbsSyn ) -> HappyWrap145
1032happyOut145 x = Happy_GHC_Exts.unsafeCoerce# x
1033{-# INLINE happyOut145 #-}
1034newtype HappyWrap146 = HappyWrap146 (Located ([AddAnn]
1035                    ,(Located StringLiteral, Located RdrName, LHsSigType GhcPs)))
1036happyIn146 :: (Located ([AddAnn]
1037                    ,(Located StringLiteral, Located RdrName, LHsSigType GhcPs))) -> (HappyAbsSyn )
1038happyIn146 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap146 x)
1039{-# INLINE happyIn146 #-}
1040happyOut146 :: (HappyAbsSyn ) -> HappyWrap146
1041happyOut146 x = Happy_GHC_Exts.unsafeCoerce# x
1042{-# INLINE happyOut146 #-}
1043newtype HappyWrap147 = HappyWrap147 (([AddAnn], Maybe (LHsType GhcPs)))
1044happyIn147 :: (([AddAnn], Maybe (LHsType GhcPs))) -> (HappyAbsSyn )
1045happyIn147 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap147 x)
1046{-# INLINE happyIn147 #-}
1047happyOut147 :: (HappyAbsSyn ) -> HappyWrap147
1048happyOut147 x = Happy_GHC_Exts.unsafeCoerce# x
1049{-# INLINE happyOut147 #-}
1050newtype HappyWrap148 = HappyWrap148 (([AddAnn], Maybe (Located RdrName)))
1051happyIn148 :: (([AddAnn], Maybe (Located RdrName))) -> (HappyAbsSyn )
1052happyIn148 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap148 x)
1053{-# INLINE happyIn148 #-}
1054happyOut148 :: (HappyAbsSyn ) -> HappyWrap148
1055happyOut148 x = Happy_GHC_Exts.unsafeCoerce# x
1056{-# INLINE happyOut148 #-}
1057newtype HappyWrap149 = HappyWrap149 (LHsType GhcPs)
1058happyIn149 :: (LHsType GhcPs) -> (HappyAbsSyn )
1059happyIn149 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap149 x)
1060{-# INLINE happyIn149 #-}
1061happyOut149 :: (HappyAbsSyn ) -> HappyWrap149
1062happyOut149 x = Happy_GHC_Exts.unsafeCoerce# x
1063{-# INLINE happyOut149 #-}
1064newtype HappyWrap150 = HappyWrap150 (LHsType GhcPs)
1065happyIn150 :: (LHsType GhcPs) -> (HappyAbsSyn )
1066happyIn150 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap150 x)
1067{-# INLINE happyIn150 #-}
1068happyOut150 :: (HappyAbsSyn ) -> HappyWrap150
1069happyOut150 x = Happy_GHC_Exts.unsafeCoerce# x
1070{-# INLINE happyOut150 #-}
1071newtype HappyWrap151 = HappyWrap151 (Located [Located RdrName])
1072happyIn151 :: (Located [Located RdrName]) -> (HappyAbsSyn )
1073happyIn151 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap151 x)
1074{-# INLINE happyIn151 #-}
1075happyOut151 :: (HappyAbsSyn ) -> HappyWrap151
1076happyOut151 x = Happy_GHC_Exts.unsafeCoerce# x
1077{-# INLINE happyOut151 #-}
1078newtype HappyWrap152 = HappyWrap152 ((OrdList (LHsSigType GhcPs)))
1079happyIn152 :: ((OrdList (LHsSigType GhcPs))) -> (HappyAbsSyn )
1080happyIn152 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap152 x)
1081{-# INLINE happyIn152 #-}
1082happyOut152 :: (HappyAbsSyn ) -> HappyWrap152
1083happyOut152 x = Happy_GHC_Exts.unsafeCoerce# x
1084{-# INLINE happyOut152 #-}
1085newtype HappyWrap153 = HappyWrap153 (Located ([AddAnn], SourceText, SrcUnpackedness))
1086happyIn153 :: (Located ([AddAnn], SourceText, SrcUnpackedness)) -> (HappyAbsSyn )
1087happyIn153 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap153 x)
1088{-# INLINE happyIn153 #-}
1089happyOut153 :: (HappyAbsSyn ) -> HappyWrap153
1090happyOut153 x = Happy_GHC_Exts.unsafeCoerce# x
1091{-# INLINE happyOut153 #-}
1092newtype HappyWrap154 = HappyWrap154 ((AddAnn, ForallVisFlag))
1093happyIn154 :: ((AddAnn, ForallVisFlag)) -> (HappyAbsSyn )
1094happyIn154 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap154 x)
1095{-# INLINE happyIn154 #-}
1096happyOut154 :: (HappyAbsSyn ) -> HappyWrap154
1097happyOut154 x = Happy_GHC_Exts.unsafeCoerce# x
1098{-# INLINE happyOut154 #-}
1099newtype HappyWrap155 = HappyWrap155 (LHsType GhcPs)
1100happyIn155 :: (LHsType GhcPs) -> (HappyAbsSyn )
1101happyIn155 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap155 x)
1102{-# INLINE happyIn155 #-}
1103happyOut155 :: (HappyAbsSyn ) -> HappyWrap155
1104happyOut155 x = Happy_GHC_Exts.unsafeCoerce# x
1105{-# INLINE happyOut155 #-}
1106newtype HappyWrap156 = HappyWrap156 (LHsType GhcPs)
1107happyIn156 :: (LHsType GhcPs) -> (HappyAbsSyn )
1108happyIn156 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap156 x)
1109{-# INLINE happyIn156 #-}
1110happyOut156 :: (HappyAbsSyn ) -> HappyWrap156
1111happyOut156 x = Happy_GHC_Exts.unsafeCoerce# x
1112{-# INLINE happyOut156 #-}
1113newtype HappyWrap157 = HappyWrap157 (LHsType GhcPs)
1114happyIn157 :: (LHsType GhcPs) -> (HappyAbsSyn )
1115happyIn157 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap157 x)
1116{-# INLINE happyIn157 #-}
1117happyOut157 :: (HappyAbsSyn ) -> HappyWrap157
1118happyOut157 x = Happy_GHC_Exts.unsafeCoerce# x
1119{-# INLINE happyOut157 #-}
1120newtype HappyWrap158 = HappyWrap158 (LHsType GhcPs)
1121happyIn158 :: (LHsType GhcPs) -> (HappyAbsSyn )
1122happyIn158 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap158 x)
1123{-# INLINE happyIn158 #-}
1124happyOut158 :: (HappyAbsSyn ) -> HappyWrap158
1125happyOut158 x = Happy_GHC_Exts.unsafeCoerce# x
1126{-# INLINE happyOut158 #-}
1127newtype HappyWrap159 = HappyWrap159 (LHsContext GhcPs)
1128happyIn159 :: (LHsContext GhcPs) -> (HappyAbsSyn )
1129happyIn159 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap159 x)
1130{-# INLINE happyIn159 #-}
1131happyOut159 :: (HappyAbsSyn ) -> HappyWrap159
1132happyOut159 x = Happy_GHC_Exts.unsafeCoerce# x
1133{-# INLINE happyOut159 #-}
1134newtype HappyWrap160 = HappyWrap160 (LHsContext GhcPs)
1135happyIn160 :: (LHsContext GhcPs) -> (HappyAbsSyn )
1136happyIn160 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap160 x)
1137{-# INLINE happyIn160 #-}
1138happyOut160 :: (HappyAbsSyn ) -> HappyWrap160
1139happyOut160 x = Happy_GHC_Exts.unsafeCoerce# x
1140{-# INLINE happyOut160 #-}
1141newtype HappyWrap161 = HappyWrap161 (LHsType GhcPs)
1142happyIn161 :: (LHsType GhcPs) -> (HappyAbsSyn )
1143happyIn161 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap161 x)
1144{-# INLINE happyIn161 #-}
1145happyOut161 :: (HappyAbsSyn ) -> HappyWrap161
1146happyOut161 x = Happy_GHC_Exts.unsafeCoerce# x
1147{-# INLINE happyOut161 #-}
1148newtype HappyWrap162 = HappyWrap162 (LHsType GhcPs)
1149happyIn162 :: (LHsType GhcPs) -> (HappyAbsSyn )
1150happyIn162 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap162 x)
1151{-# INLINE happyIn162 #-}
1152happyOut162 :: (HappyAbsSyn ) -> HappyWrap162
1153happyOut162 x = Happy_GHC_Exts.unsafeCoerce# x
1154{-# INLINE happyOut162 #-}
1155newtype HappyWrap163 = HappyWrap163 (LHsType GhcPs)
1156happyIn163 :: (LHsType GhcPs) -> (HappyAbsSyn )
1157happyIn163 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap163 x)
1158{-# INLINE happyIn163 #-}
1159happyOut163 :: (HappyAbsSyn ) -> HappyWrap163
1160happyOut163 x = Happy_GHC_Exts.unsafeCoerce# x
1161{-# INLINE happyOut163 #-}
1162newtype HappyWrap164 = HappyWrap164 (Located [Located TyEl])
1163happyIn164 :: (Located [Located TyEl]) -> (HappyAbsSyn )
1164happyIn164 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap164 x)
1165{-# INLINE happyIn164 #-}
1166happyOut164 :: (HappyAbsSyn ) -> HappyWrap164
1167happyOut164 x = Happy_GHC_Exts.unsafeCoerce# x
1168{-# INLINE happyOut164 #-}
1169newtype HappyWrap165 = HappyWrap165 (Located TyEl)
1170happyIn165 :: (Located TyEl) -> (HappyAbsSyn )
1171happyIn165 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap165 x)
1172{-# INLINE happyIn165 #-}
1173happyOut165 :: (HappyAbsSyn ) -> HappyWrap165
1174happyOut165 x = Happy_GHC_Exts.unsafeCoerce# x
1175{-# INLINE happyOut165 #-}
1176newtype HappyWrap166 = HappyWrap166 (LHsType GhcPs)
1177happyIn166 :: (LHsType GhcPs) -> (HappyAbsSyn )
1178happyIn166 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap166 x)
1179{-# INLINE happyIn166 #-}
1180happyOut166 :: (HappyAbsSyn ) -> HappyWrap166
1181happyOut166 x = Happy_GHC_Exts.unsafeCoerce# x
1182{-# INLINE happyOut166 #-}
1183newtype HappyWrap167 = HappyWrap167 ([Located TyEl])
1184happyIn167 :: ([Located TyEl]) -> (HappyAbsSyn )
1185happyIn167 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap167 x)
1186{-# INLINE happyIn167 #-}
1187happyOut167 :: (HappyAbsSyn ) -> HappyWrap167
1188happyOut167 x = Happy_GHC_Exts.unsafeCoerce# x
1189{-# INLINE happyOut167 #-}
1190newtype HappyWrap168 = HappyWrap168 (Located TyEl)
1191happyIn168 :: (Located TyEl) -> (HappyAbsSyn )
1192happyIn168 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap168 x)
1193{-# INLINE happyIn168 #-}
1194happyOut168 :: (HappyAbsSyn ) -> HappyWrap168
1195happyOut168 x = Happy_GHC_Exts.unsafeCoerce# x
1196{-# INLINE happyOut168 #-}
1197newtype HappyWrap169 = HappyWrap169 (LHsType GhcPs)
1198happyIn169 :: (LHsType GhcPs) -> (HappyAbsSyn )
1199happyIn169 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap169 x)
1200{-# INLINE happyIn169 #-}
1201happyOut169 :: (HappyAbsSyn ) -> HappyWrap169
1202happyOut169 x = Happy_GHC_Exts.unsafeCoerce# x
1203{-# INLINE happyOut169 #-}
1204newtype HappyWrap170 = HappyWrap170 (LHsSigType GhcPs)
1205happyIn170 :: (LHsSigType GhcPs) -> (HappyAbsSyn )
1206happyIn170 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap170 x)
1207{-# INLINE happyIn170 #-}
1208happyOut170 :: (HappyAbsSyn ) -> HappyWrap170
1209happyOut170 x = Happy_GHC_Exts.unsafeCoerce# x
1210{-# INLINE happyOut170 #-}
1211newtype HappyWrap171 = HappyWrap171 ([LHsSigType GhcPs])
1212happyIn171 :: ([LHsSigType GhcPs]) -> (HappyAbsSyn )
1213happyIn171 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap171 x)
1214{-# INLINE happyIn171 #-}
1215happyOut171 :: (HappyAbsSyn ) -> HappyWrap171
1216happyOut171 x = Happy_GHC_Exts.unsafeCoerce# x
1217{-# INLINE happyOut171 #-}
1218newtype HappyWrap172 = HappyWrap172 ([LHsType GhcPs])
1219happyIn172 :: ([LHsType GhcPs]) -> (HappyAbsSyn )
1220happyIn172 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap172 x)
1221{-# INLINE happyIn172 #-}
1222happyOut172 :: (HappyAbsSyn ) -> HappyWrap172
1223happyOut172 x = Happy_GHC_Exts.unsafeCoerce# x
1224{-# INLINE happyOut172 #-}
1225newtype HappyWrap173 = HappyWrap173 ([LHsType GhcPs])
1226happyIn173 :: ([LHsType GhcPs]) -> (HappyAbsSyn )
1227happyIn173 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap173 x)
1228{-# INLINE happyIn173 #-}
1229happyOut173 :: (HappyAbsSyn ) -> HappyWrap173
1230happyOut173 x = Happy_GHC_Exts.unsafeCoerce# x
1231{-# INLINE happyOut173 #-}
1232newtype HappyWrap174 = HappyWrap174 ([LHsType GhcPs])
1233happyIn174 :: ([LHsType GhcPs]) -> (HappyAbsSyn )
1234happyIn174 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap174 x)
1235{-# INLINE happyIn174 #-}
1236happyOut174 :: (HappyAbsSyn ) -> HappyWrap174
1237happyOut174 x = Happy_GHC_Exts.unsafeCoerce# x
1238{-# INLINE happyOut174 #-}
1239newtype HappyWrap175 = HappyWrap175 ([LHsTyVarBndr GhcPs])
1240happyIn175 :: ([LHsTyVarBndr GhcPs]) -> (HappyAbsSyn )
1241happyIn175 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap175 x)
1242{-# INLINE happyIn175 #-}
1243happyOut175 :: (HappyAbsSyn ) -> HappyWrap175
1244happyOut175 x = Happy_GHC_Exts.unsafeCoerce# x
1245{-# INLINE happyOut175 #-}
1246newtype HappyWrap176 = HappyWrap176 (LHsTyVarBndr GhcPs)
1247happyIn176 :: (LHsTyVarBndr GhcPs) -> (HappyAbsSyn )
1248happyIn176 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap176 x)
1249{-# INLINE happyIn176 #-}
1250happyOut176 :: (HappyAbsSyn ) -> HappyWrap176
1251happyOut176 x = Happy_GHC_Exts.unsafeCoerce# x
1252{-# INLINE happyOut176 #-}
1253newtype HappyWrap177 = HappyWrap177 (Located ([AddAnn],[Located (FunDep (Located RdrName))]))
1254happyIn177 :: (Located ([AddAnn],[Located (FunDep (Located RdrName))])) -> (HappyAbsSyn )
1255happyIn177 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap177 x)
1256{-# INLINE happyIn177 #-}
1257happyOut177 :: (HappyAbsSyn ) -> HappyWrap177
1258happyOut177 x = Happy_GHC_Exts.unsafeCoerce# x
1259{-# INLINE happyOut177 #-}
1260newtype HappyWrap178 = HappyWrap178 (Located [Located (FunDep (Located RdrName))])
1261happyIn178 :: (Located [Located (FunDep (Located RdrName))]) -> (HappyAbsSyn )
1262happyIn178 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap178 x)
1263{-# INLINE happyIn178 #-}
1264happyOut178 :: (HappyAbsSyn ) -> HappyWrap178
1265happyOut178 x = Happy_GHC_Exts.unsafeCoerce# x
1266{-# INLINE happyOut178 #-}
1267newtype HappyWrap179 = HappyWrap179 (Located (FunDep (Located RdrName)))
1268happyIn179 :: (Located (FunDep (Located RdrName))) -> (HappyAbsSyn )
1269happyIn179 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap179 x)
1270{-# INLINE happyIn179 #-}
1271happyOut179 :: (HappyAbsSyn ) -> HappyWrap179
1272happyOut179 x = Happy_GHC_Exts.unsafeCoerce# x
1273{-# INLINE happyOut179 #-}
1274newtype HappyWrap180 = HappyWrap180 (Located [Located RdrName])
1275happyIn180 :: (Located [Located RdrName]) -> (HappyAbsSyn )
1276happyIn180 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap180 x)
1277{-# INLINE happyIn180 #-}
1278happyOut180 :: (HappyAbsSyn ) -> HappyWrap180
1279happyOut180 x = Happy_GHC_Exts.unsafeCoerce# x
1280{-# INLINE happyOut180 #-}
1281newtype HappyWrap181 = HappyWrap181 (LHsKind GhcPs)
1282happyIn181 :: (LHsKind GhcPs) -> (HappyAbsSyn )
1283happyIn181 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap181 x)
1284{-# INLINE happyIn181 #-}
1285happyOut181 :: (HappyAbsSyn ) -> HappyWrap181
1286happyOut181 x = Happy_GHC_Exts.unsafeCoerce# x
1287{-# INLINE happyOut181 #-}
1288newtype HappyWrap182 = HappyWrap182 (Located ([AddAnn]
1289                          ,[LConDecl GhcPs]))
1290happyIn182 :: (Located ([AddAnn]
1291                          ,[LConDecl GhcPs])) -> (HappyAbsSyn )
1292happyIn182 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap182 x)
1293{-# INLINE happyIn182 #-}
1294happyOut182 :: (HappyAbsSyn ) -> HappyWrap182
1295happyOut182 x = Happy_GHC_Exts.unsafeCoerce# x
1296{-# INLINE happyOut182 #-}
1297newtype HappyWrap183 = HappyWrap183 (Located [LConDecl GhcPs])
1298happyIn183 :: (Located [LConDecl GhcPs]) -> (HappyAbsSyn )
1299happyIn183 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap183 x)
1300{-# INLINE happyIn183 #-}
1301happyOut183 :: (HappyAbsSyn ) -> HappyWrap183
1302happyOut183 x = Happy_GHC_Exts.unsafeCoerce# x
1303{-# INLINE happyOut183 #-}
1304newtype HappyWrap184 = HappyWrap184 (LConDecl GhcPs)
1305happyIn184 :: (LConDecl GhcPs) -> (HappyAbsSyn )
1306happyIn184 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap184 x)
1307{-# INLINE happyIn184 #-}
1308happyOut184 :: (HappyAbsSyn ) -> HappyWrap184
1309happyOut184 x = Happy_GHC_Exts.unsafeCoerce# x
1310{-# INLINE happyOut184 #-}
1311newtype HappyWrap185 = HappyWrap185 (LConDecl GhcPs)
1312happyIn185 :: (LConDecl GhcPs) -> (HappyAbsSyn )
1313happyIn185 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap185 x)
1314{-# INLINE happyIn185 #-}
1315happyOut185 :: (HappyAbsSyn ) -> HappyWrap185
1316happyOut185 x = Happy_GHC_Exts.unsafeCoerce# x
1317{-# INLINE happyOut185 #-}
1318newtype HappyWrap186 = HappyWrap186 (Located ([AddAnn],[LConDecl GhcPs]))
1319happyIn186 :: (Located ([AddAnn],[LConDecl GhcPs])) -> (HappyAbsSyn )
1320happyIn186 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap186 x)
1321{-# INLINE happyIn186 #-}
1322happyOut186 :: (HappyAbsSyn ) -> HappyWrap186
1323happyOut186 x = Happy_GHC_Exts.unsafeCoerce# x
1324{-# INLINE happyOut186 #-}
1325newtype HappyWrap187 = HappyWrap187 (Located [LConDecl GhcPs])
1326happyIn187 :: (Located [LConDecl GhcPs]) -> (HappyAbsSyn )
1327happyIn187 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap187 x)
1328{-# INLINE happyIn187 #-}
1329happyOut187 :: (HappyAbsSyn ) -> HappyWrap187
1330happyOut187 x = Happy_GHC_Exts.unsafeCoerce# x
1331{-# INLINE happyOut187 #-}
1332newtype HappyWrap188 = HappyWrap188 (LConDecl GhcPs)
1333happyIn188 :: (LConDecl GhcPs) -> (HappyAbsSyn )
1334happyIn188 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap188 x)
1335{-# INLINE happyIn188 #-}
1336happyOut188 :: (HappyAbsSyn ) -> HappyWrap188
1337happyOut188 x = Happy_GHC_Exts.unsafeCoerce# x
1338{-# INLINE happyOut188 #-}
1339newtype HappyWrap189 = HappyWrap189 (Located ([AddAnn], Maybe [LHsTyVarBndr GhcPs]))
1340happyIn189 :: (Located ([AddAnn], Maybe [LHsTyVarBndr GhcPs])) -> (HappyAbsSyn )
1341happyIn189 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap189 x)
1342{-# INLINE happyIn189 #-}
1343happyOut189 :: (HappyAbsSyn ) -> HappyWrap189
1344happyOut189 x = Happy_GHC_Exts.unsafeCoerce# x
1345{-# INLINE happyOut189 #-}
1346newtype HappyWrap190 = HappyWrap190 (Located (Located RdrName, HsConDeclDetails GhcPs, Maybe LHsDocString))
1347happyIn190 :: (Located (Located RdrName, HsConDeclDetails GhcPs, Maybe LHsDocString)) -> (HappyAbsSyn )
1348happyIn190 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap190 x)
1349{-# INLINE happyIn190 #-}
1350happyOut190 :: (HappyAbsSyn ) -> HappyWrap190
1351happyOut190 x = Happy_GHC_Exts.unsafeCoerce# x
1352{-# INLINE happyOut190 #-}
1353newtype HappyWrap191 = HappyWrap191 ([LConDeclField GhcPs])
1354happyIn191 :: ([LConDeclField GhcPs]) -> (HappyAbsSyn )
1355happyIn191 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap191 x)
1356{-# INLINE happyIn191 #-}
1357happyOut191 :: (HappyAbsSyn ) -> HappyWrap191
1358happyOut191 x = Happy_GHC_Exts.unsafeCoerce# x
1359{-# INLINE happyOut191 #-}
1360newtype HappyWrap192 = HappyWrap192 ([LConDeclField GhcPs])
1361happyIn192 :: ([LConDeclField GhcPs]) -> (HappyAbsSyn )
1362happyIn192 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap192 x)
1363{-# INLINE happyIn192 #-}
1364happyOut192 :: (HappyAbsSyn ) -> HappyWrap192
1365happyOut192 x = Happy_GHC_Exts.unsafeCoerce# x
1366{-# INLINE happyOut192 #-}
1367newtype HappyWrap193 = HappyWrap193 (LConDeclField GhcPs)
1368happyIn193 :: (LConDeclField GhcPs) -> (HappyAbsSyn )
1369happyIn193 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap193 x)
1370{-# INLINE happyIn193 #-}
1371happyOut193 :: (HappyAbsSyn ) -> HappyWrap193
1372happyOut193 x = Happy_GHC_Exts.unsafeCoerce# x
1373{-# INLINE happyOut193 #-}
1374newtype HappyWrap194 = HappyWrap194 (HsDeriving GhcPs)
1375happyIn194 :: (HsDeriving GhcPs) -> (HappyAbsSyn )
1376happyIn194 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap194 x)
1377{-# INLINE happyIn194 #-}
1378happyOut194 :: (HappyAbsSyn ) -> HappyWrap194
1379happyOut194 x = Happy_GHC_Exts.unsafeCoerce# x
1380{-# INLINE happyOut194 #-}
1381newtype HappyWrap195 = HappyWrap195 (HsDeriving GhcPs)
1382happyIn195 :: (HsDeriving GhcPs) -> (HappyAbsSyn )
1383happyIn195 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap195 x)
1384{-# INLINE happyIn195 #-}
1385happyOut195 :: (HappyAbsSyn ) -> HappyWrap195
1386happyOut195 x = Happy_GHC_Exts.unsafeCoerce# x
1387{-# INLINE happyOut195 #-}
1388newtype HappyWrap196 = HappyWrap196 (LHsDerivingClause GhcPs)
1389happyIn196 :: (LHsDerivingClause GhcPs) -> (HappyAbsSyn )
1390happyIn196 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap196 x)
1391{-# INLINE happyIn196 #-}
1392happyOut196 :: (HappyAbsSyn ) -> HappyWrap196
1393happyOut196 x = Happy_GHC_Exts.unsafeCoerce# x
1394{-# INLINE happyOut196 #-}
1395newtype HappyWrap197 = HappyWrap197 (Located [LHsSigType GhcPs])
1396happyIn197 :: (Located [LHsSigType GhcPs]) -> (HappyAbsSyn )
1397happyIn197 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap197 x)
1398{-# INLINE happyIn197 #-}
1399happyOut197 :: (HappyAbsSyn ) -> HappyWrap197
1400happyOut197 x = Happy_GHC_Exts.unsafeCoerce# x
1401{-# INLINE happyOut197 #-}
1402newtype HappyWrap198 = HappyWrap198 (LHsDecl GhcPs)
1403happyIn198 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
1404happyIn198 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap198 x)
1405{-# INLINE happyIn198 #-}
1406happyOut198 :: (HappyAbsSyn ) -> HappyWrap198
1407happyOut198 x = Happy_GHC_Exts.unsafeCoerce# x
1408{-# INLINE happyOut198 #-}
1409newtype HappyWrap199 = HappyWrap199 (LDocDecl)
1410happyIn199 :: (LDocDecl) -> (HappyAbsSyn )
1411happyIn199 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap199 x)
1412{-# INLINE happyIn199 #-}
1413happyOut199 :: (HappyAbsSyn ) -> HappyWrap199
1414happyOut199 x = Happy_GHC_Exts.unsafeCoerce# x
1415{-# INLINE happyOut199 #-}
1416newtype HappyWrap200 = HappyWrap200 (LHsDecl GhcPs)
1417happyIn200 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
1418happyIn200 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap200 x)
1419{-# INLINE happyIn200 #-}
1420happyOut200 :: (HappyAbsSyn ) -> HappyWrap200
1421happyOut200 x = Happy_GHC_Exts.unsafeCoerce# x
1422{-# INLINE happyOut200 #-}
1423newtype HappyWrap201 = HappyWrap201 (LHsDecl GhcPs)
1424happyIn201 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
1425happyIn201 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap201 x)
1426{-# INLINE happyIn201 #-}
1427happyOut201 :: (HappyAbsSyn ) -> HappyWrap201
1428happyOut201 x = Happy_GHC_Exts.unsafeCoerce# x
1429{-# INLINE happyOut201 #-}
1430newtype HappyWrap202 = HappyWrap202 (Located ([AddAnn],GRHSs GhcPs (LHsExpr GhcPs)))
1431happyIn202 :: (Located ([AddAnn],GRHSs GhcPs (LHsExpr GhcPs))) -> (HappyAbsSyn )
1432happyIn202 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap202 x)
1433{-# INLINE happyIn202 #-}
1434happyOut202 :: (HappyAbsSyn ) -> HappyWrap202
1435happyOut202 x = Happy_GHC_Exts.unsafeCoerce# x
1436{-# INLINE happyOut202 #-}
1437newtype HappyWrap203 = HappyWrap203 (Located [LGRHS GhcPs (LHsExpr GhcPs)])
1438happyIn203 :: (Located [LGRHS GhcPs (LHsExpr GhcPs)]) -> (HappyAbsSyn )
1439happyIn203 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap203 x)
1440{-# INLINE happyIn203 #-}
1441happyOut203 :: (HappyAbsSyn ) -> HappyWrap203
1442happyOut203 x = Happy_GHC_Exts.unsafeCoerce# x
1443{-# INLINE happyOut203 #-}
1444newtype HappyWrap204 = HappyWrap204 (LGRHS GhcPs (LHsExpr GhcPs))
1445happyIn204 :: (LGRHS GhcPs (LHsExpr GhcPs)) -> (HappyAbsSyn )
1446happyIn204 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap204 x)
1447{-# INLINE happyIn204 #-}
1448happyOut204 :: (HappyAbsSyn ) -> HappyWrap204
1449happyOut204 x = Happy_GHC_Exts.unsafeCoerce# x
1450{-# INLINE happyOut204 #-}
1451newtype HappyWrap205 = HappyWrap205 (LHsDecl GhcPs)
1452happyIn205 :: (LHsDecl GhcPs) -> (HappyAbsSyn )
1453happyIn205 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap205 x)
1454{-# INLINE happyIn205 #-}
1455happyOut205 :: (HappyAbsSyn ) -> HappyWrap205
1456happyOut205 x = Happy_GHC_Exts.unsafeCoerce# x
1457{-# INLINE happyOut205 #-}
1458newtype HappyWrap206 = HappyWrap206 (([AddAnn],Maybe Activation))
1459happyIn206 :: (([AddAnn],Maybe Activation)) -> (HappyAbsSyn )
1460happyIn206 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap206 x)
1461{-# INLINE happyIn206 #-}
1462happyOut206 :: (HappyAbsSyn ) -> HappyWrap206
1463happyOut206 x = Happy_GHC_Exts.unsafeCoerce# x
1464{-# INLINE happyOut206 #-}
1465newtype HappyWrap207 = HappyWrap207 (([AddAnn],Activation))
1466happyIn207 :: (([AddAnn],Activation)) -> (HappyAbsSyn )
1467happyIn207 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap207 x)
1468{-# INLINE happyIn207 #-}
1469happyOut207 :: (HappyAbsSyn ) -> HappyWrap207
1470happyOut207 x = Happy_GHC_Exts.unsafeCoerce# x
1471{-# INLINE happyOut207 #-}
1472newtype HappyWrap208 = HappyWrap208 (Located (HsSplice GhcPs))
1473happyIn208 :: (Located (HsSplice GhcPs)) -> (HappyAbsSyn )
1474happyIn208 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap208 x)
1475{-# INLINE happyIn208 #-}
1476happyOut208 :: (HappyAbsSyn ) -> HappyWrap208
1477happyOut208 x = Happy_GHC_Exts.unsafeCoerce# x
1478{-# INLINE happyOut208 #-}
1479newtype HappyWrap209 = HappyWrap209 (ECP)
1480happyIn209 :: (ECP) -> (HappyAbsSyn )
1481happyIn209 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap209 x)
1482{-# INLINE happyIn209 #-}
1483happyOut209 :: (HappyAbsSyn ) -> HappyWrap209
1484happyOut209 x = Happy_GHC_Exts.unsafeCoerce# x
1485{-# INLINE happyOut209 #-}
1486newtype HappyWrap210 = HappyWrap210 (ECP)
1487happyIn210 :: (ECP) -> (HappyAbsSyn )
1488happyIn210 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap210 x)
1489{-# INLINE happyIn210 #-}
1490happyOut210 :: (HappyAbsSyn ) -> HappyWrap210
1491happyOut210 x = Happy_GHC_Exts.unsafeCoerce# x
1492{-# INLINE happyOut210 #-}
1493newtype HappyWrap211 = HappyWrap211 (ECP)
1494happyIn211 :: (ECP) -> (HappyAbsSyn )
1495happyIn211 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap211 x)
1496{-# INLINE happyIn211 #-}
1497happyOut211 :: (HappyAbsSyn ) -> HappyWrap211
1498happyOut211 x = Happy_GHC_Exts.unsafeCoerce# x
1499{-# INLINE happyOut211 #-}
1500newtype HappyWrap212 = HappyWrap212 (ECP)
1501happyIn212 :: (ECP) -> (HappyAbsSyn )
1502happyIn212 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap212 x)
1503{-# INLINE happyIn212 #-}
1504happyOut212 :: (HappyAbsSyn ) -> HappyWrap212
1505happyOut212 x = Happy_GHC_Exts.unsafeCoerce# x
1506{-# INLINE happyOut212 #-}
1507newtype HappyWrap213 = HappyWrap213 (ECP)
1508happyIn213 :: (ECP) -> (HappyAbsSyn )
1509happyIn213 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap213 x)
1510{-# INLINE happyIn213 #-}
1511happyOut213 :: (HappyAbsSyn ) -> HappyWrap213
1512happyOut213 x = Happy_GHC_Exts.unsafeCoerce# x
1513{-# INLINE happyOut213 #-}
1514newtype HappyWrap214 = HappyWrap214 (([Located Token],Bool))
1515happyIn214 :: (([Located Token],Bool)) -> (HappyAbsSyn )
1516happyIn214 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap214 x)
1517{-# INLINE happyIn214 #-}
1518happyOut214 :: (HappyAbsSyn ) -> HappyWrap214
1519happyOut214 x = Happy_GHC_Exts.unsafeCoerce# x
1520{-# INLINE happyOut214 #-}
1521newtype HappyWrap215 = HappyWrap215 (Located (([AddAnn],SourceText),StringLiteral))
1522happyIn215 :: (Located (([AddAnn],SourceText),StringLiteral)) -> (HappyAbsSyn )
1523happyIn215 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap215 x)
1524{-# INLINE happyIn215 #-}
1525happyOut215 :: (HappyAbsSyn ) -> HappyWrap215
1526happyOut215 x = Happy_GHC_Exts.unsafeCoerce# x
1527{-# INLINE happyOut215 #-}
1528newtype HappyWrap216 = HappyWrap216 (Located ( (([AddAnn],SourceText),(StringLiteral,(Int,Int),(Int,Int))),
1529                         ((SourceText,SourceText),(SourceText,SourceText))
1530                       ))
1531happyIn216 :: (Located ( (([AddAnn],SourceText),(StringLiteral,(Int,Int),(Int,Int))),
1532                         ((SourceText,SourceText),(SourceText,SourceText))
1533                       )) -> (HappyAbsSyn )
1534happyIn216 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap216 x)
1535{-# INLINE happyIn216 #-}
1536happyOut216 :: (HappyAbsSyn ) -> HappyWrap216
1537happyOut216 x = Happy_GHC_Exts.unsafeCoerce# x
1538{-# INLINE happyOut216 #-}
1539newtype HappyWrap217 = HappyWrap217 (ECP)
1540happyIn217 :: (ECP) -> (HappyAbsSyn )
1541happyIn217 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap217 x)
1542{-# INLINE happyIn217 #-}
1543happyOut217 :: (HappyAbsSyn ) -> HappyWrap217
1544happyOut217 x = Happy_GHC_Exts.unsafeCoerce# x
1545{-# INLINE happyOut217 #-}
1546newtype HappyWrap218 = HappyWrap218 (ECP)
1547happyIn218 :: (ECP) -> (HappyAbsSyn )
1548happyIn218 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap218 x)
1549{-# INLINE happyIn218 #-}
1550happyOut218 :: (HappyAbsSyn ) -> HappyWrap218
1551happyOut218 x = Happy_GHC_Exts.unsafeCoerce# x
1552{-# INLINE happyOut218 #-}
1553newtype HappyWrap219 = HappyWrap219 (ECP)
1554happyIn219 :: (ECP) -> (HappyAbsSyn )
1555happyIn219 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap219 x)
1556{-# INLINE happyIn219 #-}
1557happyOut219 :: (HappyAbsSyn ) -> HappyWrap219
1558happyOut219 x = Happy_GHC_Exts.unsafeCoerce# x
1559{-# INLINE happyOut219 #-}
1560newtype HappyWrap220 = HappyWrap220 (ECP)
1561happyIn220 :: (ECP) -> (HappyAbsSyn )
1562happyIn220 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap220 x)
1563{-# INLINE happyIn220 #-}
1564happyOut220 :: (HappyAbsSyn ) -> HappyWrap220
1565happyOut220 x = Happy_GHC_Exts.unsafeCoerce# x
1566{-# INLINE happyOut220 #-}
1567newtype HappyWrap221 = HappyWrap221 (LHsExpr GhcPs)
1568happyIn221 :: (LHsExpr GhcPs) -> (HappyAbsSyn )
1569happyIn221 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap221 x)
1570{-# INLINE happyIn221 #-}
1571happyOut221 :: (HappyAbsSyn ) -> HappyWrap221
1572happyOut221 x = Happy_GHC_Exts.unsafeCoerce# x
1573{-# INLINE happyOut221 #-}
1574newtype HappyWrap222 = HappyWrap222 (Located (HsSplice GhcPs))
1575happyIn222 :: (Located (HsSplice GhcPs)) -> (HappyAbsSyn )
1576happyIn222 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap222 x)
1577{-# INLINE happyIn222 #-}
1578happyOut222 :: (HappyAbsSyn ) -> HappyWrap222
1579happyOut222 x = Happy_GHC_Exts.unsafeCoerce# x
1580{-# INLINE happyOut222 #-}
1581newtype HappyWrap223 = HappyWrap223 (Located (HsSplice GhcPs))
1582happyIn223 :: (Located (HsSplice GhcPs)) -> (HappyAbsSyn )
1583happyIn223 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap223 x)
1584{-# INLINE happyIn223 #-}
1585happyOut223 :: (HappyAbsSyn ) -> HappyWrap223
1586happyOut223 x = Happy_GHC_Exts.unsafeCoerce# x
1587{-# INLINE happyOut223 #-}
1588newtype HappyWrap224 = HappyWrap224 ([LHsCmdTop GhcPs])
1589happyIn224 :: ([LHsCmdTop GhcPs]) -> (HappyAbsSyn )
1590happyIn224 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap224 x)
1591{-# INLINE happyIn224 #-}
1592happyOut224 :: (HappyAbsSyn ) -> HappyWrap224
1593happyOut224 x = Happy_GHC_Exts.unsafeCoerce# x
1594{-# INLINE happyOut224 #-}
1595newtype HappyWrap225 = HappyWrap225 (LHsCmdTop GhcPs)
1596happyIn225 :: (LHsCmdTop GhcPs) -> (HappyAbsSyn )
1597happyIn225 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap225 x)
1598{-# INLINE happyIn225 #-}
1599happyOut225 :: (HappyAbsSyn ) -> HappyWrap225
1600happyOut225 x = Happy_GHC_Exts.unsafeCoerce# x
1601{-# INLINE happyOut225 #-}
1602newtype HappyWrap226 = HappyWrap226 (([AddAnn],[LHsDecl GhcPs]))
1603happyIn226 :: (([AddAnn],[LHsDecl GhcPs])) -> (HappyAbsSyn )
1604happyIn226 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap226 x)
1605{-# INLINE happyIn226 #-}
1606happyOut226 :: (HappyAbsSyn ) -> HappyWrap226
1607happyOut226 x = Happy_GHC_Exts.unsafeCoerce# x
1608{-# INLINE happyOut226 #-}
1609newtype HappyWrap227 = HappyWrap227 ([LHsDecl GhcPs])
1610happyIn227 :: ([LHsDecl GhcPs]) -> (HappyAbsSyn )
1611happyIn227 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap227 x)
1612{-# INLINE happyIn227 #-}
1613happyOut227 :: (HappyAbsSyn ) -> HappyWrap227
1614happyOut227 x = Happy_GHC_Exts.unsafeCoerce# x
1615{-# INLINE happyOut227 #-}
1616newtype HappyWrap228 = HappyWrap228 (ECP)
1617happyIn228 :: (ECP) -> (HappyAbsSyn )
1618happyIn228 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap228 x)
1619{-# INLINE happyIn228 #-}
1620happyOut228 :: (HappyAbsSyn ) -> HappyWrap228
1621happyOut228 x = Happy_GHC_Exts.unsafeCoerce# x
1622{-# INLINE happyOut228 #-}
1623newtype HappyWrap229 = HappyWrap229 (forall b. DisambECP b => PV ([AddAnn],SumOrTuple b))
1624happyIn229 :: (forall b. DisambECP b => PV ([AddAnn],SumOrTuple b)) -> (HappyAbsSyn )
1625happyIn229 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap229 x)
1626{-# INLINE happyIn229 #-}
1627happyOut229 :: (HappyAbsSyn ) -> HappyWrap229
1628happyOut229 x = Happy_GHC_Exts.unsafeCoerce# x
1629{-# INLINE happyOut229 #-}
1630newtype HappyWrap230 = HappyWrap230 (forall b. DisambECP b => PV (SrcSpan,[Located (Maybe (Located b))]))
1631happyIn230 :: (forall b. DisambECP b => PV (SrcSpan,[Located (Maybe (Located b))])) -> (HappyAbsSyn )
1632happyIn230 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap230 x)
1633{-# INLINE happyIn230 #-}
1634happyOut230 :: (HappyAbsSyn ) -> HappyWrap230
1635happyOut230 x = Happy_GHC_Exts.unsafeCoerce# x
1636{-# INLINE happyOut230 #-}
1637newtype HappyWrap231 = HappyWrap231 (forall b. DisambECP b => PV [Located (Maybe (Located b))])
1638happyIn231 :: (forall b. DisambECP b => PV [Located (Maybe (Located b))]) -> (HappyAbsSyn )
1639happyIn231 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap231 x)
1640{-# INLINE happyIn231 #-}
1641happyOut231 :: (HappyAbsSyn ) -> HappyWrap231
1642happyOut231 x = Happy_GHC_Exts.unsafeCoerce# x
1643{-# INLINE happyOut231 #-}
1644newtype HappyWrap232 = HappyWrap232 (forall b. DisambECP b => SrcSpan -> PV (Located b))
1645happyIn232 :: (forall b. DisambECP b => SrcSpan -> PV (Located b)) -> (HappyAbsSyn )
1646happyIn232 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap232 x)
1647{-# INLINE happyIn232 #-}
1648happyOut232 :: (HappyAbsSyn ) -> HappyWrap232
1649happyOut232 x = Happy_GHC_Exts.unsafeCoerce# x
1650{-# INLINE happyOut232 #-}
1651newtype HappyWrap233 = HappyWrap233 (forall b. DisambECP b => PV [Located b])
1652happyIn233 :: (forall b. DisambECP b => PV [Located b]) -> (HappyAbsSyn )
1653happyIn233 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap233 x)
1654{-# INLINE happyIn233 #-}
1655happyOut233 :: (HappyAbsSyn ) -> HappyWrap233
1656happyOut233 x = Happy_GHC_Exts.unsafeCoerce# x
1657{-# INLINE happyOut233 #-}
1658newtype HappyWrap234 = HappyWrap234 (Located [LStmt GhcPs (LHsExpr GhcPs)])
1659happyIn234 :: (Located [LStmt GhcPs (LHsExpr GhcPs)]) -> (HappyAbsSyn )
1660happyIn234 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap234 x)
1661{-# INLINE happyIn234 #-}
1662happyOut234 :: (HappyAbsSyn ) -> HappyWrap234
1663happyOut234 x = Happy_GHC_Exts.unsafeCoerce# x
1664{-# INLINE happyOut234 #-}
1665newtype HappyWrap235 = HappyWrap235 (Located [[LStmt GhcPs (LHsExpr GhcPs)]])
1666happyIn235 :: (Located [[LStmt GhcPs (LHsExpr GhcPs)]]) -> (HappyAbsSyn )
1667happyIn235 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap235 x)
1668{-# INLINE happyIn235 #-}
1669happyOut235 :: (HappyAbsSyn ) -> HappyWrap235
1670happyOut235 x = Happy_GHC_Exts.unsafeCoerce# x
1671{-# INLINE happyOut235 #-}
1672newtype HappyWrap236 = HappyWrap236 (Located [LStmt GhcPs (LHsExpr GhcPs)])
1673happyIn236 :: (Located [LStmt GhcPs (LHsExpr GhcPs)]) -> (HappyAbsSyn )
1674happyIn236 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap236 x)
1675{-# INLINE happyIn236 #-}
1676happyOut236 :: (HappyAbsSyn ) -> HappyWrap236
1677happyOut236 x = Happy_GHC_Exts.unsafeCoerce# x
1678{-# INLINE happyOut236 #-}
1679newtype HappyWrap237 = HappyWrap237 (Located ([AddAnn],[LStmt GhcPs (LHsExpr GhcPs)] -> Stmt GhcPs (LHsExpr GhcPs)))
1680happyIn237 :: (Located ([AddAnn],[LStmt GhcPs (LHsExpr GhcPs)] -> Stmt GhcPs (LHsExpr GhcPs))) -> (HappyAbsSyn )
1681happyIn237 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap237 x)
1682{-# INLINE happyIn237 #-}
1683happyOut237 :: (HappyAbsSyn ) -> HappyWrap237
1684happyOut237 x = Happy_GHC_Exts.unsafeCoerce# x
1685{-# INLINE happyOut237 #-}
1686newtype HappyWrap238 = HappyWrap238 (Located [LStmt GhcPs (LHsExpr GhcPs)])
1687happyIn238 :: (Located [LStmt GhcPs (LHsExpr GhcPs)]) -> (HappyAbsSyn )
1688happyIn238 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap238 x)
1689{-# INLINE happyIn238 #-}
1690happyOut238 :: (HappyAbsSyn ) -> HappyWrap238
1691happyOut238 x = Happy_GHC_Exts.unsafeCoerce# x
1692{-# INLINE happyOut238 #-}
1693newtype HappyWrap239 = HappyWrap239 (Located [LStmt GhcPs (LHsExpr GhcPs)])
1694happyIn239 :: (Located [LStmt GhcPs (LHsExpr GhcPs)]) -> (HappyAbsSyn )
1695happyIn239 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap239 x)
1696{-# INLINE happyIn239 #-}
1697happyOut239 :: (HappyAbsSyn ) -> HappyWrap239
1698happyOut239 x = Happy_GHC_Exts.unsafeCoerce# x
1699{-# INLINE happyOut239 #-}
1700newtype HappyWrap240 = HappyWrap240 (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)])))
1701happyIn240 :: (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)]))) -> (HappyAbsSyn )
1702happyIn240 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap240 x)
1703{-# INLINE happyIn240 #-}
1704happyOut240 :: (HappyAbsSyn ) -> HappyWrap240
1705happyOut240 x = Happy_GHC_Exts.unsafeCoerce# x
1706{-# INLINE happyOut240 #-}
1707newtype HappyWrap241 = HappyWrap241 (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)])))
1708happyIn241 :: (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)]))) -> (HappyAbsSyn )
1709happyIn241 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap241 x)
1710{-# INLINE happyIn241 #-}
1711happyOut241 :: (HappyAbsSyn ) -> HappyWrap241
1712happyOut241 x = Happy_GHC_Exts.unsafeCoerce# x
1713{-# INLINE happyOut241 #-}
1714newtype HappyWrap242 = HappyWrap242 (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)])))
1715happyIn242 :: (forall b. DisambECP b => PV (Located ([AddAnn],[LMatch GhcPs (Located b)]))) -> (HappyAbsSyn )
1716happyIn242 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap242 x)
1717{-# INLINE happyIn242 #-}
1718happyOut242 :: (HappyAbsSyn ) -> HappyWrap242
1719happyOut242 x = Happy_GHC_Exts.unsafeCoerce# x
1720{-# INLINE happyOut242 #-}
1721newtype HappyWrap243 = HappyWrap243 (forall b. DisambECP b => PV (LMatch GhcPs (Located b)))
1722happyIn243 :: (forall b. DisambECP b => PV (LMatch GhcPs (Located b))) -> (HappyAbsSyn )
1723happyIn243 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap243 x)
1724{-# INLINE happyIn243 #-}
1725happyOut243 :: (HappyAbsSyn ) -> HappyWrap243
1726happyOut243 x = Happy_GHC_Exts.unsafeCoerce# x
1727{-# INLINE happyOut243 #-}
1728newtype HappyWrap244 = HappyWrap244 (forall b. DisambECP b => PV (Located ([AddAnn],GRHSs GhcPs (Located b))))
1729happyIn244 :: (forall b. DisambECP b => PV (Located ([AddAnn],GRHSs GhcPs (Located b)))) -> (HappyAbsSyn )
1730happyIn244 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap244 x)
1731{-# INLINE happyIn244 #-}
1732happyOut244 :: (HappyAbsSyn ) -> HappyWrap244
1733happyOut244 x = Happy_GHC_Exts.unsafeCoerce# x
1734{-# INLINE happyOut244 #-}
1735newtype HappyWrap245 = HappyWrap245 (forall b. DisambECP b => PV (Located [LGRHS GhcPs (Located b)]))
1736happyIn245 :: (forall b. DisambECP b => PV (Located [LGRHS GhcPs (Located b)])) -> (HappyAbsSyn )
1737happyIn245 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap245 x)
1738{-# INLINE happyIn245 #-}
1739happyOut245 :: (HappyAbsSyn ) -> HappyWrap245
1740happyOut245 x = Happy_GHC_Exts.unsafeCoerce# x
1741{-# INLINE happyOut245 #-}
1742newtype HappyWrap246 = HappyWrap246 (forall b. DisambECP b => PV (Located [LGRHS GhcPs (Located b)]))
1743happyIn246 :: (forall b. DisambECP b => PV (Located [LGRHS GhcPs (Located b)])) -> (HappyAbsSyn )
1744happyIn246 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap246 x)
1745{-# INLINE happyIn246 #-}
1746happyOut246 :: (HappyAbsSyn ) -> HappyWrap246
1747happyOut246 x = Happy_GHC_Exts.unsafeCoerce# x
1748{-# INLINE happyOut246 #-}
1749newtype HappyWrap247 = HappyWrap247 (Located ([AddAnn],[LGRHS GhcPs (LHsExpr GhcPs)]))
1750happyIn247 :: (Located ([AddAnn],[LGRHS GhcPs (LHsExpr GhcPs)])) -> (HappyAbsSyn )
1751happyIn247 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap247 x)
1752{-# INLINE happyIn247 #-}
1753happyOut247 :: (HappyAbsSyn ) -> HappyWrap247
1754happyOut247 x = Happy_GHC_Exts.unsafeCoerce# x
1755{-# INLINE happyOut247 #-}
1756newtype HappyWrap248 = HappyWrap248 (forall b. DisambECP b => PV (LGRHS GhcPs (Located b)))
1757happyIn248 :: (forall b. DisambECP b => PV (LGRHS GhcPs (Located b))) -> (HappyAbsSyn )
1758happyIn248 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap248 x)
1759{-# INLINE happyIn248 #-}
1760happyOut248 :: (HappyAbsSyn ) -> HappyWrap248
1761happyOut248 x = Happy_GHC_Exts.unsafeCoerce# x
1762{-# INLINE happyOut248 #-}
1763newtype HappyWrap249 = HappyWrap249 (LPat GhcPs)
1764happyIn249 :: (LPat GhcPs) -> (HappyAbsSyn )
1765happyIn249 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap249 x)
1766{-# INLINE happyIn249 #-}
1767happyOut249 :: (HappyAbsSyn ) -> HappyWrap249
1768happyOut249 x = Happy_GHC_Exts.unsafeCoerce# x
1769{-# INLINE happyOut249 #-}
1770newtype HappyWrap250 = HappyWrap250 (LPat GhcPs)
1771happyIn250 :: (LPat GhcPs) -> (HappyAbsSyn )
1772happyIn250 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap250 x)
1773{-# INLINE happyIn250 #-}
1774happyOut250 :: (HappyAbsSyn ) -> HappyWrap250
1775happyOut250 x = Happy_GHC_Exts.unsafeCoerce# x
1776{-# INLINE happyOut250 #-}
1777newtype HappyWrap251 = HappyWrap251 (LPat GhcPs)
1778happyIn251 :: (LPat GhcPs) -> (HappyAbsSyn )
1779happyIn251 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap251 x)
1780{-# INLINE happyIn251 #-}
1781happyOut251 :: (HappyAbsSyn ) -> HappyWrap251
1782happyOut251 x = Happy_GHC_Exts.unsafeCoerce# x
1783{-# INLINE happyOut251 #-}
1784newtype HappyWrap252 = HappyWrap252 ([LPat GhcPs])
1785happyIn252 :: ([LPat GhcPs]) -> (HappyAbsSyn )
1786happyIn252 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap252 x)
1787{-# INLINE happyIn252 #-}
1788happyOut252 :: (HappyAbsSyn ) -> HappyWrap252
1789happyOut252 x = Happy_GHC_Exts.unsafeCoerce# x
1790{-# INLINE happyOut252 #-}
1791newtype HappyWrap253 = HappyWrap253 (forall b. DisambECP b => PV (Located ([AddAnn],[LStmt GhcPs (Located b)])))
1792happyIn253 :: (forall b. DisambECP b => PV (Located ([AddAnn],[LStmt GhcPs (Located b)]))) -> (HappyAbsSyn )
1793happyIn253 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap253 x)
1794{-# INLINE happyIn253 #-}
1795happyOut253 :: (HappyAbsSyn ) -> HappyWrap253
1796happyOut253 x = Happy_GHC_Exts.unsafeCoerce# x
1797{-# INLINE happyOut253 #-}
1798newtype HappyWrap254 = HappyWrap254 (forall b. DisambECP b => PV (Located ([AddAnn],[LStmt GhcPs (Located b)])))
1799happyIn254 :: (forall b. DisambECP b => PV (Located ([AddAnn],[LStmt GhcPs (Located b)]))) -> (HappyAbsSyn )
1800happyIn254 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap254 x)
1801{-# INLINE happyIn254 #-}
1802happyOut254 :: (HappyAbsSyn ) -> HappyWrap254
1803happyOut254 x = Happy_GHC_Exts.unsafeCoerce# x
1804{-# INLINE happyOut254 #-}
1805newtype HappyWrap255 = HappyWrap255 (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
1806happyIn255 :: (Maybe (LStmt GhcPs (LHsExpr GhcPs))) -> (HappyAbsSyn )
1807happyIn255 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap255 x)
1808{-# INLINE happyIn255 #-}
1809happyOut255 :: (HappyAbsSyn ) -> HappyWrap255
1810happyOut255 x = Happy_GHC_Exts.unsafeCoerce# x
1811{-# INLINE happyOut255 #-}
1812newtype HappyWrap256 = HappyWrap256 (LStmt GhcPs (LHsExpr GhcPs))
1813happyIn256 :: (LStmt GhcPs (LHsExpr GhcPs)) -> (HappyAbsSyn )
1814happyIn256 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap256 x)
1815{-# INLINE happyIn256 #-}
1816happyOut256 :: (HappyAbsSyn ) -> HappyWrap256
1817happyOut256 x = Happy_GHC_Exts.unsafeCoerce# x
1818{-# INLINE happyOut256 #-}
1819newtype HappyWrap257 = HappyWrap257 (forall b. DisambECP b => PV (LStmt GhcPs (Located b)))
1820happyIn257 :: (forall b. DisambECP b => PV (LStmt GhcPs (Located b))) -> (HappyAbsSyn )
1821happyIn257 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap257 x)
1822{-# INLINE happyIn257 #-}
1823happyOut257 :: (HappyAbsSyn ) -> HappyWrap257
1824happyOut257 x = Happy_GHC_Exts.unsafeCoerce# x
1825{-# INLINE happyOut257 #-}
1826newtype HappyWrap258 = HappyWrap258 (forall b. DisambECP b => PV (LStmt GhcPs (Located b)))
1827happyIn258 :: (forall b. DisambECP b => PV (LStmt GhcPs (Located b))) -> (HappyAbsSyn )
1828happyIn258 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap258 x)
1829{-# INLINE happyIn258 #-}
1830happyOut258 :: (HappyAbsSyn ) -> HappyWrap258
1831happyOut258 x = Happy_GHC_Exts.unsafeCoerce# x
1832{-# INLINE happyOut258 #-}
1833newtype HappyWrap259 = HappyWrap259 (forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)))
1834happyIn259 :: (forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan))) -> (HappyAbsSyn )
1835happyIn259 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap259 x)
1836{-# INLINE happyIn259 #-}
1837happyOut259 :: (HappyAbsSyn ) -> HappyWrap259
1838happyOut259 x = Happy_GHC_Exts.unsafeCoerce# x
1839{-# INLINE happyOut259 #-}
1840newtype HappyWrap260 = HappyWrap260 (forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)))
1841happyIn260 :: (forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan))) -> (HappyAbsSyn )
1842happyIn260 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap260 x)
1843{-# INLINE happyIn260 #-}
1844happyOut260 :: (HappyAbsSyn ) -> HappyWrap260
1845happyOut260 x = Happy_GHC_Exts.unsafeCoerce# x
1846{-# INLINE happyOut260 #-}
1847newtype HappyWrap261 = HappyWrap261 (forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)))
1848happyIn261 :: (forall b. DisambECP b => PV (LHsRecField GhcPs (Located b))) -> (HappyAbsSyn )
1849happyIn261 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap261 x)
1850{-# INLINE happyIn261 #-}
1851happyOut261 :: (HappyAbsSyn ) -> HappyWrap261
1852happyOut261 x = Happy_GHC_Exts.unsafeCoerce# x
1853{-# INLINE happyOut261 #-}
1854newtype HappyWrap262 = HappyWrap262 (Located [LIPBind GhcPs])
1855happyIn262 :: (Located [LIPBind GhcPs]) -> (HappyAbsSyn )
1856happyIn262 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap262 x)
1857{-# INLINE happyIn262 #-}
1858happyOut262 :: (HappyAbsSyn ) -> HappyWrap262
1859happyOut262 x = Happy_GHC_Exts.unsafeCoerce# x
1860{-# INLINE happyOut262 #-}
1861newtype HappyWrap263 = HappyWrap263 (LIPBind GhcPs)
1862happyIn263 :: (LIPBind GhcPs) -> (HappyAbsSyn )
1863happyIn263 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap263 x)
1864{-# INLINE happyIn263 #-}
1865happyOut263 :: (HappyAbsSyn ) -> HappyWrap263
1866happyOut263 x = Happy_GHC_Exts.unsafeCoerce# x
1867{-# INLINE happyOut263 #-}
1868newtype HappyWrap264 = HappyWrap264 (Located HsIPName)
1869happyIn264 :: (Located HsIPName) -> (HappyAbsSyn )
1870happyIn264 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap264 x)
1871{-# INLINE happyIn264 #-}
1872happyOut264 :: (HappyAbsSyn ) -> HappyWrap264
1873happyOut264 x = Happy_GHC_Exts.unsafeCoerce# x
1874{-# INLINE happyOut264 #-}
1875newtype HappyWrap265 = HappyWrap265 (Located FastString)
1876happyIn265 :: (Located FastString) -> (HappyAbsSyn )
1877happyIn265 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap265 x)
1878{-# INLINE happyIn265 #-}
1879happyOut265 :: (HappyAbsSyn ) -> HappyWrap265
1880happyOut265 x = Happy_GHC_Exts.unsafeCoerce# x
1881{-# INLINE happyOut265 #-}
1882newtype HappyWrap266 = HappyWrap266 (LBooleanFormula (Located RdrName))
1883happyIn266 :: (LBooleanFormula (Located RdrName)) -> (HappyAbsSyn )
1884happyIn266 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap266 x)
1885{-# INLINE happyIn266 #-}
1886happyOut266 :: (HappyAbsSyn ) -> HappyWrap266
1887happyOut266 x = Happy_GHC_Exts.unsafeCoerce# x
1888{-# INLINE happyOut266 #-}
1889newtype HappyWrap267 = HappyWrap267 (LBooleanFormula (Located RdrName))
1890happyIn267 :: (LBooleanFormula (Located RdrName)) -> (HappyAbsSyn )
1891happyIn267 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap267 x)
1892{-# INLINE happyIn267 #-}
1893happyOut267 :: (HappyAbsSyn ) -> HappyWrap267
1894happyOut267 x = Happy_GHC_Exts.unsafeCoerce# x
1895{-# INLINE happyOut267 #-}
1896newtype HappyWrap268 = HappyWrap268 (LBooleanFormula (Located RdrName))
1897happyIn268 :: (LBooleanFormula (Located RdrName)) -> (HappyAbsSyn )
1898happyIn268 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap268 x)
1899{-# INLINE happyIn268 #-}
1900happyOut268 :: (HappyAbsSyn ) -> HappyWrap268
1901happyOut268 x = Happy_GHC_Exts.unsafeCoerce# x
1902{-# INLINE happyOut268 #-}
1903newtype HappyWrap269 = HappyWrap269 ([LBooleanFormula (Located RdrName)])
1904happyIn269 :: ([LBooleanFormula (Located RdrName)]) -> (HappyAbsSyn )
1905happyIn269 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap269 x)
1906{-# INLINE happyIn269 #-}
1907happyOut269 :: (HappyAbsSyn ) -> HappyWrap269
1908happyOut269 x = Happy_GHC_Exts.unsafeCoerce# x
1909{-# INLINE happyOut269 #-}
1910newtype HappyWrap270 = HappyWrap270 (LBooleanFormula (Located RdrName))
1911happyIn270 :: (LBooleanFormula (Located RdrName)) -> (HappyAbsSyn )
1912happyIn270 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap270 x)
1913{-# INLINE happyIn270 #-}
1914happyOut270 :: (HappyAbsSyn ) -> HappyWrap270
1915happyOut270 x = Happy_GHC_Exts.unsafeCoerce# x
1916{-# INLINE happyOut270 #-}
1917newtype HappyWrap271 = HappyWrap271 (Located [Located RdrName])
1918happyIn271 :: (Located [Located RdrName]) -> (HappyAbsSyn )
1919happyIn271 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap271 x)
1920{-# INLINE happyIn271 #-}
1921happyOut271 :: (HappyAbsSyn ) -> HappyWrap271
1922happyOut271 x = Happy_GHC_Exts.unsafeCoerce# x
1923{-# INLINE happyOut271 #-}
1924newtype HappyWrap272 = HappyWrap272 (Located RdrName)
1925happyIn272 :: (Located RdrName) -> (HappyAbsSyn )
1926happyIn272 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap272 x)
1927{-# INLINE happyIn272 #-}
1928happyOut272 :: (HappyAbsSyn ) -> HappyWrap272
1929happyOut272 x = Happy_GHC_Exts.unsafeCoerce# x
1930{-# INLINE happyOut272 #-}
1931newtype HappyWrap273 = HappyWrap273 (Located RdrName)
1932happyIn273 :: (Located RdrName) -> (HappyAbsSyn )
1933happyIn273 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap273 x)
1934{-# INLINE happyIn273 #-}
1935happyOut273 :: (HappyAbsSyn ) -> HappyWrap273
1936happyOut273 x = Happy_GHC_Exts.unsafeCoerce# x
1937{-# INLINE happyOut273 #-}
1938newtype HappyWrap274 = HappyWrap274 (Located RdrName)
1939happyIn274 :: (Located RdrName) -> (HappyAbsSyn )
1940happyIn274 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap274 x)
1941{-# INLINE happyIn274 #-}
1942happyOut274 :: (HappyAbsSyn ) -> HappyWrap274
1943happyOut274 x = Happy_GHC_Exts.unsafeCoerce# x
1944{-# INLINE happyOut274 #-}
1945newtype HappyWrap275 = HappyWrap275 (Located RdrName)
1946happyIn275 :: (Located RdrName) -> (HappyAbsSyn )
1947happyIn275 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap275 x)
1948{-# INLINE happyIn275 #-}
1949happyOut275 :: (HappyAbsSyn ) -> HappyWrap275
1950happyOut275 x = Happy_GHC_Exts.unsafeCoerce# x
1951{-# INLINE happyOut275 #-}
1952newtype HappyWrap276 = HappyWrap276 (Located RdrName)
1953happyIn276 :: (Located RdrName) -> (HappyAbsSyn )
1954happyIn276 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap276 x)
1955{-# INLINE happyIn276 #-}
1956happyOut276 :: (HappyAbsSyn ) -> HappyWrap276
1957happyOut276 x = Happy_GHC_Exts.unsafeCoerce# x
1958{-# INLINE happyOut276 #-}
1959newtype HappyWrap277 = HappyWrap277 (Located [Located RdrName])
1960happyIn277 :: (Located [Located RdrName]) -> (HappyAbsSyn )
1961happyIn277 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap277 x)
1962{-# INLINE happyIn277 #-}
1963happyOut277 :: (HappyAbsSyn ) -> HappyWrap277
1964happyOut277 x = Happy_GHC_Exts.unsafeCoerce# x
1965{-# INLINE happyOut277 #-}
1966newtype HappyWrap278 = HappyWrap278 (Located DataCon)
1967happyIn278 :: (Located DataCon) -> (HappyAbsSyn )
1968happyIn278 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap278 x)
1969{-# INLINE happyIn278 #-}
1970happyOut278 :: (HappyAbsSyn ) -> HappyWrap278
1971happyOut278 x = Happy_GHC_Exts.unsafeCoerce# x
1972{-# INLINE happyOut278 #-}
1973newtype HappyWrap279 = HappyWrap279 (Located DataCon)
1974happyIn279 :: (Located DataCon) -> (HappyAbsSyn )
1975happyIn279 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap279 x)
1976{-# INLINE happyIn279 #-}
1977happyOut279 :: (HappyAbsSyn ) -> HappyWrap279
1978happyOut279 x = Happy_GHC_Exts.unsafeCoerce# x
1979{-# INLINE happyOut279 #-}
1980newtype HappyWrap280 = HappyWrap280 (Located RdrName)
1981happyIn280 :: (Located RdrName) -> (HappyAbsSyn )
1982happyIn280 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap280 x)
1983{-# INLINE happyIn280 #-}
1984happyOut280 :: (HappyAbsSyn ) -> HappyWrap280
1985happyOut280 x = Happy_GHC_Exts.unsafeCoerce# x
1986{-# INLINE happyOut280 #-}
1987newtype HappyWrap281 = HappyWrap281 (Located RdrName)
1988happyIn281 :: (Located RdrName) -> (HappyAbsSyn )
1989happyIn281 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap281 x)
1990{-# INLINE happyIn281 #-}
1991happyOut281 :: (HappyAbsSyn ) -> HappyWrap281
1992happyOut281 x = Happy_GHC_Exts.unsafeCoerce# x
1993{-# INLINE happyOut281 #-}
1994newtype HappyWrap282 = HappyWrap282 (Located RdrName)
1995happyIn282 :: (Located RdrName) -> (HappyAbsSyn )
1996happyIn282 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap282 x)
1997{-# INLINE happyIn282 #-}
1998happyOut282 :: (HappyAbsSyn ) -> HappyWrap282
1999happyOut282 x = Happy_GHC_Exts.unsafeCoerce# x
2000{-# INLINE happyOut282 #-}
2001newtype HappyWrap283 = HappyWrap283 (Located RdrName)
2002happyIn283 :: (Located RdrName) -> (HappyAbsSyn )
2003happyIn283 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap283 x)
2004{-# INLINE happyIn283 #-}
2005happyOut283 :: (HappyAbsSyn ) -> HappyWrap283
2006happyOut283 x = Happy_GHC_Exts.unsafeCoerce# x
2007{-# INLINE happyOut283 #-}
2008newtype HappyWrap284 = HappyWrap284 (Located RdrName)
2009happyIn284 :: (Located RdrName) -> (HappyAbsSyn )
2010happyIn284 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap284 x)
2011{-# INLINE happyIn284 #-}
2012happyOut284 :: (HappyAbsSyn ) -> HappyWrap284
2013happyOut284 x = Happy_GHC_Exts.unsafeCoerce# x
2014{-# INLINE happyOut284 #-}
2015newtype HappyWrap285 = HappyWrap285 (Located RdrName)
2016happyIn285 :: (Located RdrName) -> (HappyAbsSyn )
2017happyIn285 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap285 x)
2018{-# INLINE happyIn285 #-}
2019happyOut285 :: (HappyAbsSyn ) -> HappyWrap285
2020happyOut285 x = Happy_GHC_Exts.unsafeCoerce# x
2021{-# INLINE happyOut285 #-}
2022newtype HappyWrap286 = HappyWrap286 (Located RdrName)
2023happyIn286 :: (Located RdrName) -> (HappyAbsSyn )
2024happyIn286 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap286 x)
2025{-# INLINE happyIn286 #-}
2026happyOut286 :: (HappyAbsSyn ) -> HappyWrap286
2027happyOut286 x = Happy_GHC_Exts.unsafeCoerce# x
2028{-# INLINE happyOut286 #-}
2029newtype HappyWrap287 = HappyWrap287 (Located RdrName)
2030happyIn287 :: (Located RdrName) -> (HappyAbsSyn )
2031happyIn287 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap287 x)
2032{-# INLINE happyIn287 #-}
2033happyOut287 :: (HappyAbsSyn ) -> HappyWrap287
2034happyOut287 x = Happy_GHC_Exts.unsafeCoerce# x
2035{-# INLINE happyOut287 #-}
2036newtype HappyWrap288 = HappyWrap288 (LHsType GhcPs)
2037happyIn288 :: (LHsType GhcPs) -> (HappyAbsSyn )
2038happyIn288 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap288 x)
2039{-# INLINE happyIn288 #-}
2040happyOut288 :: (HappyAbsSyn ) -> HappyWrap288
2041happyOut288 x = Happy_GHC_Exts.unsafeCoerce# x
2042{-# INLINE happyOut288 #-}
2043newtype HappyWrap289 = HappyWrap289 (Located RdrName)
2044happyIn289 :: (Located RdrName) -> (HappyAbsSyn )
2045happyIn289 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap289 x)
2046{-# INLINE happyIn289 #-}
2047happyOut289 :: (HappyAbsSyn ) -> HappyWrap289
2048happyOut289 x = Happy_GHC_Exts.unsafeCoerce# x
2049{-# INLINE happyOut289 #-}
2050newtype HappyWrap290 = HappyWrap290 (Located RdrName)
2051happyIn290 :: (Located RdrName) -> (HappyAbsSyn )
2052happyIn290 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap290 x)
2053{-# INLINE happyIn290 #-}
2054happyOut290 :: (HappyAbsSyn ) -> HappyWrap290
2055happyOut290 x = Happy_GHC_Exts.unsafeCoerce# x
2056{-# INLINE happyOut290 #-}
2057newtype HappyWrap291 = HappyWrap291 (Located RdrName)
2058happyIn291 :: (Located RdrName) -> (HappyAbsSyn )
2059happyIn291 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap291 x)
2060{-# INLINE happyIn291 #-}
2061happyOut291 :: (HappyAbsSyn ) -> HappyWrap291
2062happyOut291 x = Happy_GHC_Exts.unsafeCoerce# x
2063{-# INLINE happyOut291 #-}
2064newtype HappyWrap292 = HappyWrap292 (Located RdrName)
2065happyIn292 :: (Located RdrName) -> (HappyAbsSyn )
2066happyIn292 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap292 x)
2067{-# INLINE happyIn292 #-}
2068happyOut292 :: (HappyAbsSyn ) -> HappyWrap292
2069happyOut292 x = Happy_GHC_Exts.unsafeCoerce# x
2070{-# INLINE happyOut292 #-}
2071newtype HappyWrap293 = HappyWrap293 (Located RdrName)
2072happyIn293 :: (Located RdrName) -> (HappyAbsSyn )
2073happyIn293 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap293 x)
2074{-# INLINE happyIn293 #-}
2075happyOut293 :: (HappyAbsSyn ) -> HappyWrap293
2076happyOut293 x = Happy_GHC_Exts.unsafeCoerce# x
2077{-# INLINE happyOut293 #-}
2078newtype HappyWrap294 = HappyWrap294 (forall b. DisambInfixOp b => PV (Located b))
2079happyIn294 :: (forall b. DisambInfixOp b => PV (Located b)) -> (HappyAbsSyn )
2080happyIn294 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap294 x)
2081{-# INLINE happyIn294 #-}
2082happyOut294 :: (HappyAbsSyn ) -> HappyWrap294
2083happyOut294 x = Happy_GHC_Exts.unsafeCoerce# x
2084{-# INLINE happyOut294 #-}
2085newtype HappyWrap295 = HappyWrap295 (forall b. DisambInfixOp b => PV (Located b))
2086happyIn295 :: (forall b. DisambInfixOp b => PV (Located b)) -> (HappyAbsSyn )
2087happyIn295 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap295 x)
2088{-# INLINE happyIn295 #-}
2089happyOut295 :: (HappyAbsSyn ) -> HappyWrap295
2090happyOut295 x = Happy_GHC_Exts.unsafeCoerce# x
2091{-# INLINE happyOut295 #-}
2092newtype HappyWrap296 = HappyWrap296 (forall b. DisambInfixOp b => PV (Located b))
2093happyIn296 :: (forall b. DisambInfixOp b => PV (Located b)) -> (HappyAbsSyn )
2094happyIn296 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap296 x)
2095{-# INLINE happyIn296 #-}
2096happyOut296 :: (HappyAbsSyn ) -> HappyWrap296
2097happyOut296 x = Happy_GHC_Exts.unsafeCoerce# x
2098{-# INLINE happyOut296 #-}
2099newtype HappyWrap297 = HappyWrap297 (Located RdrName)
2100happyIn297 :: (Located RdrName) -> (HappyAbsSyn )
2101happyIn297 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap297 x)
2102{-# INLINE happyIn297 #-}
2103happyOut297 :: (HappyAbsSyn ) -> HappyWrap297
2104happyOut297 x = Happy_GHC_Exts.unsafeCoerce# x
2105{-# INLINE happyOut297 #-}
2106newtype HappyWrap298 = HappyWrap298 (Located RdrName)
2107happyIn298 :: (Located RdrName) -> (HappyAbsSyn )
2108happyIn298 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap298 x)
2109{-# INLINE happyIn298 #-}
2110happyOut298 :: (HappyAbsSyn ) -> HappyWrap298
2111happyOut298 x = Happy_GHC_Exts.unsafeCoerce# x
2112{-# INLINE happyOut298 #-}
2113newtype HappyWrap299 = HappyWrap299 (Located RdrName)
2114happyIn299 :: (Located RdrName) -> (HappyAbsSyn )
2115happyIn299 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap299 x)
2116{-# INLINE happyIn299 #-}
2117happyOut299 :: (HappyAbsSyn ) -> HappyWrap299
2118happyOut299 x = Happy_GHC_Exts.unsafeCoerce# x
2119{-# INLINE happyOut299 #-}
2120newtype HappyWrap300 = HappyWrap300 (Located RdrName)
2121happyIn300 :: (Located RdrName) -> (HappyAbsSyn )
2122happyIn300 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap300 x)
2123{-# INLINE happyIn300 #-}
2124happyOut300 :: (HappyAbsSyn ) -> HappyWrap300
2125happyOut300 x = Happy_GHC_Exts.unsafeCoerce# x
2126{-# INLINE happyOut300 #-}
2127newtype HappyWrap301 = HappyWrap301 (Located RdrName)
2128happyIn301 :: (Located RdrName) -> (HappyAbsSyn )
2129happyIn301 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap301 x)
2130{-# INLINE happyIn301 #-}
2131happyOut301 :: (HappyAbsSyn ) -> HappyWrap301
2132happyOut301 x = Happy_GHC_Exts.unsafeCoerce# x
2133{-# INLINE happyOut301 #-}
2134newtype HappyWrap302 = HappyWrap302 (Located RdrName)
2135happyIn302 :: (Located RdrName) -> (HappyAbsSyn )
2136happyIn302 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap302 x)
2137{-# INLINE happyIn302 #-}
2138happyOut302 :: (HappyAbsSyn ) -> HappyWrap302
2139happyOut302 x = Happy_GHC_Exts.unsafeCoerce# x
2140{-# INLINE happyOut302 #-}
2141newtype HappyWrap303 = HappyWrap303 (Located RdrName)
2142happyIn303 :: (Located RdrName) -> (HappyAbsSyn )
2143happyIn303 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap303 x)
2144{-# INLINE happyIn303 #-}
2145happyOut303 :: (HappyAbsSyn ) -> HappyWrap303
2146happyOut303 x = Happy_GHC_Exts.unsafeCoerce# x
2147{-# INLINE happyOut303 #-}
2148newtype HappyWrap304 = HappyWrap304 (Located RdrName)
2149happyIn304 :: (Located RdrName) -> (HappyAbsSyn )
2150happyIn304 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap304 x)
2151{-# INLINE happyIn304 #-}
2152happyOut304 :: (HappyAbsSyn ) -> HappyWrap304
2153happyOut304 x = Happy_GHC_Exts.unsafeCoerce# x
2154{-# INLINE happyOut304 #-}
2155newtype HappyWrap305 = HappyWrap305 (Located RdrName)
2156happyIn305 :: (Located RdrName) -> (HappyAbsSyn )
2157happyIn305 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap305 x)
2158{-# INLINE happyIn305 #-}
2159happyOut305 :: (HappyAbsSyn ) -> HappyWrap305
2160happyOut305 x = Happy_GHC_Exts.unsafeCoerce# x
2161{-# INLINE happyOut305 #-}
2162newtype HappyWrap306 = HappyWrap306 (Located RdrName)
2163happyIn306 :: (Located RdrName) -> (HappyAbsSyn )
2164happyIn306 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap306 x)
2165{-# INLINE happyIn306 #-}
2166happyOut306 :: (HappyAbsSyn ) -> HappyWrap306
2167happyOut306 x = Happy_GHC_Exts.unsafeCoerce# x
2168{-# INLINE happyOut306 #-}
2169newtype HappyWrap307 = HappyWrap307 (Located RdrName)
2170happyIn307 :: (Located RdrName) -> (HappyAbsSyn )
2171happyIn307 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap307 x)
2172{-# INLINE happyIn307 #-}
2173happyOut307 :: (HappyAbsSyn ) -> HappyWrap307
2174happyOut307 x = Happy_GHC_Exts.unsafeCoerce# x
2175{-# INLINE happyOut307 #-}
2176newtype HappyWrap308 = HappyWrap308 (Located RdrName)
2177happyIn308 :: (Located RdrName) -> (HappyAbsSyn )
2178happyIn308 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap308 x)
2179{-# INLINE happyIn308 #-}
2180happyOut308 :: (HappyAbsSyn ) -> HappyWrap308
2181happyOut308 x = Happy_GHC_Exts.unsafeCoerce# x
2182{-# INLINE happyOut308 #-}
2183newtype HappyWrap309 = HappyWrap309 (Located RdrName)
2184happyIn309 :: (Located RdrName) -> (HappyAbsSyn )
2185happyIn309 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap309 x)
2186{-# INLINE happyIn309 #-}
2187happyOut309 :: (HappyAbsSyn ) -> HappyWrap309
2188happyOut309 x = Happy_GHC_Exts.unsafeCoerce# x
2189{-# INLINE happyOut309 #-}
2190newtype HappyWrap310 = HappyWrap310 (Located RdrName)
2191happyIn310 :: (Located RdrName) -> (HappyAbsSyn )
2192happyIn310 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap310 x)
2193{-# INLINE happyIn310 #-}
2194happyOut310 :: (HappyAbsSyn ) -> HappyWrap310
2195happyOut310 x = Happy_GHC_Exts.unsafeCoerce# x
2196{-# INLINE happyOut310 #-}
2197newtype HappyWrap311 = HappyWrap311 (Located FastString)
2198happyIn311 :: (Located FastString) -> (HappyAbsSyn )
2199happyIn311 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap311 x)
2200{-# INLINE happyIn311 #-}
2201happyOut311 :: (HappyAbsSyn ) -> HappyWrap311
2202happyOut311 x = Happy_GHC_Exts.unsafeCoerce# x
2203{-# INLINE happyOut311 #-}
2204newtype HappyWrap312 = HappyWrap312 (Located FastString)
2205happyIn312 :: (Located FastString) -> (HappyAbsSyn )
2206happyIn312 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap312 x)
2207{-# INLINE happyIn312 #-}
2208happyOut312 :: (HappyAbsSyn ) -> HappyWrap312
2209happyOut312 x = Happy_GHC_Exts.unsafeCoerce# x
2210{-# INLINE happyOut312 #-}
2211newtype HappyWrap313 = HappyWrap313 (Located RdrName)
2212happyIn313 :: (Located RdrName) -> (HappyAbsSyn )
2213happyIn313 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap313 x)
2214{-# INLINE happyIn313 #-}
2215happyOut313 :: (HappyAbsSyn ) -> HappyWrap313
2216happyOut313 x = Happy_GHC_Exts.unsafeCoerce# x
2217{-# INLINE happyOut313 #-}
2218newtype HappyWrap314 = HappyWrap314 (Located RdrName)
2219happyIn314 :: (Located RdrName) -> (HappyAbsSyn )
2220happyIn314 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap314 x)
2221{-# INLINE happyIn314 #-}
2222happyOut314 :: (HappyAbsSyn ) -> HappyWrap314
2223happyOut314 x = Happy_GHC_Exts.unsafeCoerce# x
2224{-# INLINE happyOut314 #-}
2225newtype HappyWrap315 = HappyWrap315 (Located RdrName)
2226happyIn315 :: (Located RdrName) -> (HappyAbsSyn )
2227happyIn315 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap315 x)
2228{-# INLINE happyIn315 #-}
2229happyOut315 :: (HappyAbsSyn ) -> HappyWrap315
2230happyOut315 x = Happy_GHC_Exts.unsafeCoerce# x
2231{-# INLINE happyOut315 #-}
2232newtype HappyWrap316 = HappyWrap316 (Located RdrName)
2233happyIn316 :: (Located RdrName) -> (HappyAbsSyn )
2234happyIn316 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap316 x)
2235{-# INLINE happyIn316 #-}
2236happyOut316 :: (HappyAbsSyn ) -> HappyWrap316
2237happyOut316 x = Happy_GHC_Exts.unsafeCoerce# x
2238{-# INLINE happyOut316 #-}
2239newtype HappyWrap317 = HappyWrap317 (Located (HsLit GhcPs))
2240happyIn317 :: (Located (HsLit GhcPs)) -> (HappyAbsSyn )
2241happyIn317 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap317 x)
2242{-# INLINE happyIn317 #-}
2243happyOut317 :: (HappyAbsSyn ) -> HappyWrap317
2244happyOut317 x = Happy_GHC_Exts.unsafeCoerce# x
2245{-# INLINE happyOut317 #-}
2246newtype HappyWrap318 = HappyWrap318 (())
2247happyIn318 :: (()) -> (HappyAbsSyn )
2248happyIn318 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap318 x)
2249{-# INLINE happyIn318 #-}
2250happyOut318 :: (HappyAbsSyn ) -> HappyWrap318
2251happyOut318 x = Happy_GHC_Exts.unsafeCoerce# x
2252{-# INLINE happyOut318 #-}
2253newtype HappyWrap319 = HappyWrap319 (Located ModuleName)
2254happyIn319 :: (Located ModuleName) -> (HappyAbsSyn )
2255happyIn319 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap319 x)
2256{-# INLINE happyIn319 #-}
2257happyOut319 :: (HappyAbsSyn ) -> HappyWrap319
2258happyOut319 x = Happy_GHC_Exts.unsafeCoerce# x
2259{-# INLINE happyOut319 #-}
2260newtype HappyWrap320 = HappyWrap320 (([SrcSpan],Int))
2261happyIn320 :: (([SrcSpan],Int)) -> (HappyAbsSyn )
2262happyIn320 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap320 x)
2263{-# INLINE happyIn320 #-}
2264happyOut320 :: (HappyAbsSyn ) -> HappyWrap320
2265happyOut320 x = Happy_GHC_Exts.unsafeCoerce# x
2266{-# INLINE happyOut320 #-}
2267newtype HappyWrap321 = HappyWrap321 (([SrcSpan],Int))
2268happyIn321 :: (([SrcSpan],Int)) -> (HappyAbsSyn )
2269happyIn321 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap321 x)
2270{-# INLINE happyIn321 #-}
2271happyOut321 :: (HappyAbsSyn ) -> HappyWrap321
2272happyOut321 x = Happy_GHC_Exts.unsafeCoerce# x
2273{-# INLINE happyOut321 #-}
2274newtype HappyWrap322 = HappyWrap322 (([SrcSpan],Int))
2275happyIn322 :: (([SrcSpan],Int)) -> (HappyAbsSyn )
2276happyIn322 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap322 x)
2277{-# INLINE happyIn322 #-}
2278happyOut322 :: (HappyAbsSyn ) -> HappyWrap322
2279happyOut322 x = Happy_GHC_Exts.unsafeCoerce# x
2280{-# INLINE happyOut322 #-}
2281newtype HappyWrap323 = HappyWrap323 (LHsDocString)
2282happyIn323 :: (LHsDocString) -> (HappyAbsSyn )
2283happyIn323 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap323 x)
2284{-# INLINE happyIn323 #-}
2285happyOut323 :: (HappyAbsSyn ) -> HappyWrap323
2286happyOut323 x = Happy_GHC_Exts.unsafeCoerce# x
2287{-# INLINE happyOut323 #-}
2288newtype HappyWrap324 = HappyWrap324 (LHsDocString)
2289happyIn324 :: (LHsDocString) -> (HappyAbsSyn )
2290happyIn324 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap324 x)
2291{-# INLINE happyIn324 #-}
2292happyOut324 :: (HappyAbsSyn ) -> HappyWrap324
2293happyOut324 x = Happy_GHC_Exts.unsafeCoerce# x
2294{-# INLINE happyOut324 #-}
2295newtype HappyWrap325 = HappyWrap325 (Located (String, HsDocString))
2296happyIn325 :: (Located (String, HsDocString)) -> (HappyAbsSyn )
2297happyIn325 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap325 x)
2298{-# INLINE happyIn325 #-}
2299happyOut325 :: (HappyAbsSyn ) -> HappyWrap325
2300happyOut325 x = Happy_GHC_Exts.unsafeCoerce# x
2301{-# INLINE happyOut325 #-}
2302newtype HappyWrap326 = HappyWrap326 (Located (Int, HsDocString))
2303happyIn326 :: (Located (Int, HsDocString)) -> (HappyAbsSyn )
2304happyIn326 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap326 x)
2305{-# INLINE happyIn326 #-}
2306happyOut326 :: (HappyAbsSyn ) -> HappyWrap326
2307happyOut326 x = Happy_GHC_Exts.unsafeCoerce# x
2308{-# INLINE happyOut326 #-}
2309newtype HappyWrap327 = HappyWrap327 (Maybe LHsDocString)
2310happyIn327 :: (Maybe LHsDocString) -> (HappyAbsSyn )
2311happyIn327 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap327 x)
2312{-# INLINE happyIn327 #-}
2313happyOut327 :: (HappyAbsSyn ) -> HappyWrap327
2314happyOut327 x = Happy_GHC_Exts.unsafeCoerce# x
2315{-# INLINE happyOut327 #-}
2316newtype HappyWrap328 = HappyWrap328 (Maybe LHsDocString)
2317happyIn328 :: (Maybe LHsDocString) -> (HappyAbsSyn )
2318happyIn328 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap328 x)
2319{-# INLINE happyIn328 #-}
2320happyOut328 :: (HappyAbsSyn ) -> HappyWrap328
2321happyOut328 x = Happy_GHC_Exts.unsafeCoerce# x
2322{-# INLINE happyOut328 #-}
2323newtype HappyWrap329 = HappyWrap329 (Maybe LHsDocString)
2324happyIn329 :: (Maybe LHsDocString) -> (HappyAbsSyn )
2325happyIn329 x = Happy_GHC_Exts.unsafeCoerce# (HappyWrap329 x)
2326{-# INLINE happyIn329 #-}
2327happyOut329 :: (HappyAbsSyn ) -> HappyWrap329
2328happyOut329 x = Happy_GHC_Exts.unsafeCoerce# x
2329{-# INLINE happyOut329 #-}
2330happyInTok :: ((Located Token)) -> (HappyAbsSyn )
2331happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
2332{-# INLINE happyInTok #-}
2333happyOutTok :: (HappyAbsSyn ) -> ((Located Token))
2334happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
2335{-# INLINE happyOutTok #-}
2336
2337
2338happyExpList :: HappyAddr
2339happyExpList = HappyA# "\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc7\x1f\x1c\x00\x40\xd0\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfe\xcd\x57\xfd\xff\x97\xff\xfb\x19\x04\x41\x03\x20\x2a\x9c\xf9\xff\x7f\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x73\x11\xfd\xff\xe5\xff\x1c\x04\x41\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x1f\x7f\x70\x00\x00\x41\x03\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x80\x40\x1c\x82\x28\xe8\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x70\x08\x00\x00\x22\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfc\xf8\x84\x1f\x00\x00\x00\x00\x00\x80\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfc\xf8\x84\x1f\x00\x00\x00\x00\x81\x88\x02\x47\x30\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x29\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x75\x38\xe2\xf0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\xc6\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x18\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x80\x00\x1c\x82\x28\xe8\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\xd4\x21\x00\x41\x98\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x60\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x14\x05\x88\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7e\x00\x00\x00\x41\x00\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xe1\x07\x00\x00\x10\x04\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xe1\x07\x00\x00\x30\x24\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\x85\x1f\x00\x00\x40\x10\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x00\x00\x00\x41\x00\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xf8\x01\x00\x00\x04\x01\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x12\x74\x08\xa6\xe2\xff\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x48\xd1\x21\x88\xcb\xff\xff\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x20\x45\x87\x20\x3a\xff\xff\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x1c\x02\x00\x88\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x28\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x88\x02\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x20\x45\x87\x20\x2e\xff\xff\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\x85\x1f\x00\x00\x40\x10\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\xc0\x21\x00\x80\x98\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x80\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x20\x04\xbf\x3f\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x20\x0a\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x88\x02\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x48\xf5\xfb\x13\x7e\x00\x00\x00\x00\x00\x20\x0a\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xf8\x01\x00\x00\x04\x01\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xf8\x01\x00\x00\x04\x01\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\x85\x1f\x00\x00\x40\x10\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x1c\x02\x10\x84\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x08\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x80\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x04\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xc1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x1d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xc1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x1d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfc\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\x41\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x80\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x60\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\xc0\x3f\x00\x80\x98\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x04\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x48\xd0\x21\x88\xca\xff\xff\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x20\x45\x87\x20\x2a\xfe\xff\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x00\x00\x10\x04\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x60\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x02\x70\x08\xe2\x90\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x00\x02\x88\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x80\x00\x22\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\xcd\x45\xf4\xff\x97\xff\x73\x10\x04\x41\x03\x20\x2a\x9c\xf9\xff\x7f\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x17\xd1\xff\x5f\xfe\xcf\x41\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x50\x87\x00\x00\x62\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x35\x08\x40\x10\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x70\x08\x00\x20\x66\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x70\x08\x40\x10\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x80\x04\x1d\x82\xa8\xfc\xff\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x04\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7e\x00\x00\x00\x41\x02\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xe1\x07\x00\x00\x10\x04\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x7f\xfc\xc1\x01\x00\x04\x0d\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\xff\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xe1\x07\x00\x00\x10\x04\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x10\x00\x00\x00\x02\x88\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x00\x00\x00\x40\x20\xa2\xc0\x11\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0e\x7f\xcf\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x60\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x00\x02\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x3f\x3e\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xc1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x1d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\x70\xe0\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x18\x40\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x21\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\xd0\x00\x89\x2a\x67\xfe\x1f\x5e\x7f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x03\x30\xaa\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xf8\x01\x00\x00\x04\x09\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x48\xd0\x21\x88\x8a\xff\xff\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x4c\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x48\xd0\x21\x88\x8a\xff\xff\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x80\x04\x1d\x82\xa8\xfc\xff\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x20\x6a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf8\x37\x5f\xf5\xff\x5f\xfe\xef\x67\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x10\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x70\x08\x00\x20\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x88\x02\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x88\x02\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x1c\x02\x00\x88\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x80\x04\x1d\x82\xa8\xf8\xff\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\xd0\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x0d\x02\x00\x80\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x08\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x80\x00\x02\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x08\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\xd0\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x80\x28\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\xa2\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x80\x28\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xe1\x07\x00\x00\x10\x04\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xdf\x7c\xd5\xff\x7f\xf9\xbf\x9f\x41\x10\x34\x00\xa2\xc2\x99\xff\xff\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf4\xfb\x13\x7e\x00\x00\x00\x00\x00\x00\x02\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x3f\x3e\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x10\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x80\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x02\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x08\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x5c\x44\xff\x7f\xf9\x3f\x07\x41\x10\x34\x00\xa2\xc2\x99\xff\xff\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x08\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x80\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x80\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x40\x1d\x02\x00\x88\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\xd0\x00\x88\x2a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x7f\xfc\xc1\x01\x00\x04\x0d\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x12\x74\x08\xa2\xe2\xff\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x04\x00\x00\x80\x00\x22\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x07\x3e\xe1\x07\x00\x00\x00\x00\x00\x00\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x34\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x31\xfd\xff\xc5\x1f\x1c\x00\x40\xd0\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\xc4\xf4\xff\x17\x7f\x70\x00\x00\x41\x03\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x80\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x02\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x60\x00\x00\x00\x00\x00\x00\x20\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x02\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6e\xcd\x45\xf5\xff\x97\xff\x73\x10\x04\x41\x03\x20\x2a\x9c\xf9\xff\x7f\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x35\x17\xd5\xff\x5f\xfe\xcf\x41\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2e\xcd\x55\xf5\xff\x97\xff\x73\x10\x04\x41\x03\x20\x2a\x9c\xf9\xff\x7f\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x34\x57\xd5\xff\x5f\xfe\xcf\x41\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x3f\x3e\xe1\x07\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfd\xfe\x84\x1f\x00\x00\x00\x00\x00\x80\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xd1\xef\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x70\x08\x00\x20\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\xcd\x45\xf4\xff\x97\xff\x73\x10\x04\x41\x03\x20\x2a\x9c\xf9\xff\x7f\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x17\xd1\xff\x5f\xfe\xcf\x41\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xcf\x80\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x81\x10\xfd\xfa\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x0a\x10\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x28\x40\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xe2\xe0\xf7\x0c\x08\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x04\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x43\x03\x11\xfd\xff\xc5\x1f\x1c\x00\x40\x50\x00\x88\x0a\x67\xfe\x1f\x5e\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x0d\x44\xf4\xff\x17\x7f\x70\x00\x00\x41\x01\x20\x2a\x9c\xf9\x7f\x78\xfd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x34\x10\xd1\xff\x5f\xfc\xc1\x01\x00\x04\x05\x80\xa8\x70\xe6\xff\xe1\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x07\x3e\xe1\x07\x00\x00\x00\x00\x00\x00\x80\x01\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x52\xfd\xfe\xa4\x1f\x00\x00\x00\x00\x00\x80\x40\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x28\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x74\x08\x00\x00\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x04\x07\x3e\xe1\x07\x00\x00\x00\x00\x00\x00\x80\x01\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfc\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x40\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x00\x00\x00\x02\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x5b\x73\x51\xfd\xff\xe5\xff\x1c\x04\x41\xd0\x00\x88\x0a\x67\xfe\xff\x5f\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfc\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x87\x00\x00\x62\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xc1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x1d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x34\x57\xd5\xff\x5f\xfe\xcf\x41\x10\x04\x0d\x80\xa8\x70\xe6\xff\xff\xf5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x0c\xd0\xe1\x88\x82\xdf\x31\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf4\xe3\x13\x7e\x00\x06\x30\x40\x87\x23\x0a\x7e\xc7\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x44\xbf\x3f\xe1\x07\x00\x00\x00\x00\x00\x20\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x10\xfc\xf8\x84\x1f\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x08\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\xf7\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x0a\x10\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfd\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x33\x20\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x01\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xc1\x8f\x4f\xf8\x01\x18\x80\x00\x1d\x8e\x28\xf8\x1d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xd0\x40\x44\xff\x7f\xf1\x07\x07\x00\x10\x14\x00\xa2\xc2\x99\xff\x87\xd7\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x40\x10\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x00\x54\xbf\x3f\xe1\x07\x00\x00\x01\x00\x00\x20\x80\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x04\x40\xf0\xe3\x13\x7e\x00\x06\x20\x40\x87\x23\x0a\x7e\xc7\x00\x01\x8c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x10\x00\xd1\x8f\x4f\xf8\x01\x18\x80\x40\x1d\x8e\x38\xfc\x3d\x03\x00\x30\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\xf0\xe3\x13\x7e\x00\x00\x00\x00\x00\x00\x02\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x40\x00\x44\x3f\x3e\xe1\x07\x60\x00\x02\x74\x38\xa2\xe0\x77\x0c\x00\xc0\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x10\x00\xc1\x8f\x4f\xf8\x01\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x01\x10\xfc\xf8\x84\x1f\x80\x01\x08\xd0\xe1\x88\x82\xdf\x31\x40\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x04\x40\x70\xe0\x13\x7e\x00\x00\x00\x00\x00\x00\x00\x38\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x01\x50\xfd\xfe\x84\x1f\x00\x00\x04\x00\x00\x80\x00\x66\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x40\x80\x54\xbf\x3f\xe9\x07\x00\x00\x00\x00\x00\x20\x80\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
2340
2341{-# NOINLINE happyExpListPerState #-}
2342happyExpListPerState st =
2343    token_strs_expected
2344  where token_strs = ["error","%dummy","%start_parseModule","%start_parseSignature","%start_parseImport","%start_parseStatement","%start_parseDeclaration","%start_parseExpression","%start_parsePattern","%start_parseTypeSignature","%start_parseStmt","%start_parseIdentifier","%start_parseType","%start_parseBackpack","%start_parseHeader","identifier","backpack","units","unit","unitid","msubsts","msubst","moduleid","pkgname","litpkgname_segment","litpkgname","mayberns","rns","rn","unitbody","unitdecls","unitdecl","signature","module","maybedocheader","missing_module_keyword","implicit_top","maybemodwarning","body","body2","top","top1","header","header_body","header_body2","header_top","header_top_importdecls","maybeexports","exportlist","exportlist1","expdoclist","exp_doc","export","export_subspec","qcnames","qcnames1","qcname_ext_w_wildcard","qcname_ext","qcname","semis1","semis","importdecls","importdecls_semi","importdecl","maybe_src","maybe_safe","maybe_pkg","optqualified","maybeas","maybeimpspec","impspec","prec","infix","ops","topdecls","topdecls_semi","topdecl","cl_decl","ty_decl","standalone_kind_sig","sks_vars","inst_decl","overlap_pragma","deriv_strategy_no_via","deriv_strategy_via","deriv_standalone_strategy","opt_injective_info","injectivity_cond","inj_varids","where_type_family","ty_fam_inst_eqn_list","ty_fam_inst_eqns","ty_fam_inst_eqn","at_decl_cls","opt_family","opt_instance","at_decl_inst","data_or_newtype","opt_kind_sig","opt_datafam_kind_sig","opt_tyfam_kind_sig","opt_at_kind_inj_sig","tycl_hdr","tycl_hdr_inst","capi_ctype","stand_alone_deriving","role_annot","maybe_roles","roles","role","pattern_synonym_decl","pattern_synonym_lhs","vars0","cvars1","where_decls","pattern_synonym_sig","decl_cls","decls_cls","decllist_cls","where_cls","decl_inst","decls_inst","decllist_inst","where_inst","decls","decllist","binds","wherebinds","rules","rule","rule_activation","rule_explicit_activation","rule_foralls","rule_vars","rule_var","warnings","warning","deprecations","deprecation","strings","stringlist","annotation","fdecl","callconv","safety","fspec","opt_sig","opt_tyconsig","sigtype","sigtypedoc","sig_vars","sigtypes1","unpackedness","forall_vis_flag","ktype","ktypedoc","ctype","ctypedoc","context","constr_context","type","typedoc","constr_btype","constr_tyapps","constr_tyapp","btype","tyapps","tyapp","atype","inst_type","deriv_types","comma_types0","comma_types1","bar_types2","tv_bndrs","tv_bndr","fds","fds1","fd","varids0","kind","gadt_constrlist","gadt_constrs","gadt_constr_with_doc","gadt_constr","constrs","constrs1","constr","forall","constr_stuff","fielddecls","fielddecls1","fielddecl","maybe_derivings","derivings","deriving","deriv_clause_types","docdecl","docdecld","decl_no_th","decl","rhs","gdrhs","gdrh","sigdecl","activation","explicit_activation","quasiquote","exp","infixexp","infixexp_top","exp10_top","exp10","optSemi","scc_annot","hpc_annot","fexp","aexp","aexp1","aexp2","splice_exp","splice_untyped","splice_typed","cmdargs","acmd","cvtopbody","cvtopdecls0","texp","tup_exprs","commas_tup_tail","tup_tail","list","lexps","flattenedpquals","pquals","squals","transformqual","guardquals","guardquals1","altslist","alts","alts1","alt","alt_rhs","ralt","gdpats","ifgdpats","gdpat","pat","bindpat","apat","apats","stmtlist","stmts","maybe_stmt","e_stmt","stmt","qual","fbinds","fbinds1","fbind","dbinds","dbind","ipvar","overloaded_label","name_boolformula_opt","name_boolformula","name_boolformula_and","name_boolformula_and_list","name_boolformula_atom","namelist","name_var","qcon_nowiredlist","qcon","gen_qcon","con","con_list","sysdcon_nolist","sysdcon","conop","qconop","gtycon","ntgtycon","oqtycon","oqtycon_no_varcon","qtyconop","qtycon","qtycondoc","tycon","qtyconsym","tyconsym","op","varop","qop","qopm","hole_op","qvarop","qvaropm","tyvar","tyvarop","tyvarid","var","qvar","qvarid","varid","qvarsym","qvarsym_no_minus","qvarsym1","varsym","varsym_no_minus","special_id","special_sym","qconid","conid","qconsym","consym","literal","close","modid","commas","bars0","bars","docnext","docprev","docnamed","docsection","moduleheader","maybe_docprev","maybe_docnext","'_'","'as'","'case'","'class'","'data'","'default'","'deriving'","'do'","'else'","'hiding'","'if'","'import'","'in'","'infix'","'infixl'","'infixr'","'instance'","'let'","'module'","'newtype'","'of'","'qualified'","'then'","'type'","'where'","'forall'","'foreign'","'export'","'label'","'dynamic'","'safe'","'interruptible'","'unsafe'","'mdo'","'family'","'role'","'stdcall'","'ccall'","'capi'","'prim'","'javascript'","'proc'","'rec'","'group'","'by'","'using'","'pattern'","'static'","'stock'","'anyclass'","'via'","'unit'","'signature'","'dependency'","'{-# INLINE'","'{-# SPECIALISE'","'{-# SPECIALISE_INLINE'","'{-# SOURCE'","'{-# RULES'","'{-# CORE'","'{-# SCC'","'{-# GENERATED'","'{-# DEPRECATED'","'{-# WARNING'","'{-# UNPACK'","'{-# NOUNPACK'","'{-# ANN'","'{-# MINIMAL'","'{-# CTYPE'","'{-# OVERLAPPING'","'{-# OVERLAPPABLE'","'{-# OVERLAPS'","'{-# INCOHERENT'","'{-# COMPLETE'","'#-}'","'..'","':'","'::'","'='","'\\\\'","'lcase'","'|'","'<-'","'->'","'@'","'~'","'=>'","'-'","'!'","'*'","'-<'","'>-'","'-<<'","'>>-'","'.'","TYPEAPP","'{'","'}'","vocurly","vccurly","'['","']'","'[:'","':]'","'('","')'","'(#'","'#)'","'(|'","'|)'","';'","','","'`'","SIMPLEQUOTE","VARID","CONID","VARSYM","CONSYM","QVARID","QCONID","QVARSYM","QCONSYM","IPDUPVARID","LABELVARID","CHAR","STRING","INTEGER","RATIONAL","PRIMCHAR","PRIMSTRING","PRIMINTEGER","PRIMWORD","PRIMFLOAT","PRIMDOUBLE","DOCNEXT","DOCPREV","DOCNAMED","DOCSECTION","'[|'","'[p|'","'[t|'","'[d|'","'|]'","'[||'","'||]'","TH_ID_SPLICE","'$('","TH_ID_TY_SPLICE","'$$('","TH_TY_QUOTE","TH_QUASIQUOTE","TH_QQUASIQUOTE","%eof"]
2345        bit_start = st * 482
2346        bit_end = (st + 1) * 482
2347        read_bit = readArrayBit happyExpList
2348        bits = map read_bit [bit_start..bit_end - 1]
2349        bits_indexed = zip bits [0..481]
2350        token_strs_expected = concatMap f bits_indexed
2351        f (False, _) = []
2352        f (True, nr) = [token_strs !! nr]
2353
2354happyActOffsets :: HappyAddr
2355happyActOffsets = HappyA# "\x45\x00\xe1\xff\x33\x01\x14\x25\xcc\x19\x34\x2c\x3c\x29\x4c\x23\x14\x25\xc5\x42\x13\x3a\x2a\x00\x40\x00\xc5\x45\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x02\x00\x00\x00\x00\x68\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x23\x01\x23\x01\x00\x00\xde\x00\x5c\x01\x65\x01\x00\x00\x36\x04\x05\x41\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x4a\x00\x00\x00\x00\x00\x00\xa4\x01\xdc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x41\x0e\x00\x1d\x35\x21\x33\xa0\x33\x5f\x45\x2a\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x2c\x00\x00\x00\x00\xd3\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\x01\x47\x09\x16\x02\xc5\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x36\x02\xbd\x16\x00\x00\x00\x00\x34\x2c\x34\x2c\x2c\x2f\x00\x00\x60\x02\x00\x00\x00\x00\x00\x00\x48\x02\x83\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf1\x02\x00\x00\x00\x00\x34\x2c\x3f\x00\xac\x25\x59\x03\xca\x03\x8c\x31\xca\x03\x8c\x31\xef\x02\x24\x01\x05\x03\x94\x2e\x8c\x31\xc4\x2f\x8c\x31\x54\x20\x5c\x1d\xf4\x1d\x9a\x32\x2f\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x2c\x34\x2c\x13\x3a\xb6\x04\x34\x2c\x00\x00\x34\x2c\xfb\x44\x57\x02\x00\x00\x07\x03\x80\x03\x00\x00\x5f\x03\x6c\x03\x00\x00\x00\x00\x00\x00\xf8\x04\x7e\x03\x2f\x03\x81\x00\x2f\x03\xc5\x45\xa7\x47\x7e\x03\x8c\x1e\x00\x00\x13\x03\x8c\x31\x13\x03\x13\x03\x00\x00\x00\x00\x00\x00\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x07\x00\x00\x00\x00\x00\x00\x00\x00\x05\x41\xd0\x03\xb7\x03\xbd\x02\x9f\x04\x00\x00\x9c\x35\xf9\x00\xe2\x47\xce\x03\x0f\x48\x0f\x48\x7a\x47\x8c\x31\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x03\x00\x00\xcb\x03\x3c\x04\xd4\x03\x56\x04\xf7\x03\x88\x04\x00\x00\x00\x00\x00\x00\x4b\x04\x60\x04\x59\x00\x8f\x02\x8f\x02\xa8\x04\x8d\x04\x58\x04\x8c\x31\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8c\x31\x7b\x04\x0a\x07\x47\x01\x00\x00\x80\x00\xa6\x04\x53\x01\x00\x00\x80\x00\x54\x01\x00\x00\x90\x04\xab\x02\x0d\x49\xcc\x04\x43\x01\x37\x01\x00\x00\x1a\x04\x1a\x04\x5d\x00\xce\x04\xd4\x04\xd0\x00\x0d\x3d\x05\x41\x52\x03\x13\x3a\xe4\x04\xf0\x04\xfc\x04\x0d\x05\x00\x00\x30\x05\x00\x00\x00\x00\x00\x00\x05\x41\x13\x3a\x05\x41\x0c\x05\x0e\x05\x00\x00\x58\x04\x00\x00\xfc\x2d\x00\x00\x00\x00\x1b\x36\x8f\x43\x05\x41\x26\x05\x00\x05\x00\x00\x22\x05\xbd\x16\x96\x02\x1e\x05\x00\x00\x34\x2c\x00\x00\x00\x00\x00\x00\x49\x05\x4f\x05\x5e\x05\x64\x05\x24\x1f\xec\x20\x00\x00\xc4\x2f\x00\x00\x00\x00\x8f\x43\x1c\x05\x41\x05\x8b\x05\x00\x00\x8c\x05\x00\x00\x89\x05\x00\x00\xf2\x45\x31\x00\xc5\x45\x00\x00\xb7\x00\xc5\x45\x13\x3a\xc5\x45\x00\x00\xd6\x05\xc4\x1c\xc4\x1c\x53\x49\x9a\x36\x3b\x04\x00\x00\x00\x00\x00\x00\x00\x00\x9b\x05\x89\x09\xc6\x02\xdc\x05\x9d\x05\xa5\x05\x00\x00\x00\x00\xcf\x05\x65\x04\xdf\x05\x00\x00\x00\x00\x70\x0b\x00\x00\x00\x00\xb2\x01\xf9\x05\x00\x00\x00\x00\xbc\x1f\x00\x00\xff\x05\xf4\x01\x0a\x06\x04\x06\x00\x00\x00\x00\x5c\x30\x00\x00\x00\x00\xf4\x30\x16\x05\x8c\x31\x09\x06\x3e\x06\x40\x06\x41\x06\x00\x00\x00\x00\x44\x26\x44\x26\x28\x06\x00\x00\x87\x06\x2e\x06\x57\x00\x00\x00\x00\x00\xd4\x29\x4c\x06\x00\x00\x8a\x06\x8c\x31\x34\x2c\x8c\x45\x00\x00\x84\x41\x00\x00\x00\x00\x34\x2c\x13\x3a\x34\x2c\x34\x2c\x34\x2c\x34\x2c\x2f\x06\x30\x06\x2d\x03\x38\x06\x39\x06\x9b\x01\x3a\x06\x3b\x06\x3c\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x3a\x1f\x34\x28\x45\x36\x06\x37\x06\x3c\x01\x3d\x06\x3f\x06\x88\x03\x00\x00\xfb\x02\x42\x06\x2c\x03\x45\x06\x00\x00\xba\x01\x00\x00\x48\x06\x00\x00\xbe\x01\x00\x00\x53\x49\x00\x00\x97\x44\x00\x00\x00\x00\x4f\x00\x07\x4a\x00\x00\xc7\x32\x05\x41\x00\x00\x13\x3a\x13\x3a\x13\x3a\xb0\x00\x00\x00\x94\x0f\x54\x00\x00\x00\x4a\x06\x00\x00\x9d\x03\x9d\x03\x15\x03\x00\x00\x00\x00\x15\x03\x00\x00\x00\x00\xa2\x06\x00\x00\x00\x00\x00\x00\x00\x00\x7c\x06\x98\x06\x5f\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x06\x00\x00\x13\x3a\x00\x00\x00\x00\x3f\x01\x00\x00\x34\x03\x50\x06\x00\x00\x00\x00\x13\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x3a\x00\x00\x00\x00\x00\x00\x13\x3a\x13\x3a\x00\x00\x00\x00\x52\x06\x51\x06\x5a\x06\x61\x06\x62\x06\x63\x06\x64\x06\x68\x06\x70\x06\x71\x06\x72\x06\x73\x06\x7b\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x06\x00\x00\x77\x06\x9a\x06\x00\x00\x00\x00\x00\x00\x16\x05\x23\x02\x96\x06\x80\x06\x00\x00\x00\x00\x00\x00\xdc\x06\x00\x00\x34\x2c\x34\x2c\x61\x00\x00\x00\xe3\x00\x34\x2c\x00\x00\x00\x00\xa8\x06\x00\x00\x00\x00\x7c\x24\x34\x19\xf4\x30\xa5\x06\xe4\x23\x00\x00\x34\x2c\xdc\x26\xe4\x23\x00\x00\x8c\x06\x00\x00\x00\x00\x00\x00\x84\x21\xab\x06\x00\x00\x13\x32\x00\x00\x00\x00\x00\x00\x00\x00\xcc\x19\x59\x00\x9c\x06\x00\x00\x00\x00\x00\x00\x00\x00\x9f\x06\x00\x00\x9d\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb2\x48\x00\x00\x00\x00\xb3\x06\x00\x00\x62\x00\xbe\x06\x05\x41\x07\x4a\x87\x01\x6a\x00\x00\x00\x00\x00\x79\x0e\x00\x00\x1c\x22\xb4\x22\x68\x01\x00\x00\xc0\x06\x56\x01\x3d\x02\xc5\x06\x00\x00\xc8\x06\xc6\x06\xa0\x06\xaf\x06\xd0\x06\x00\x00\xd5\x06\xb7\x06\xb9\x06\x4a\x48\x4a\x48\x00\x00\xd9\x06\xf3\x03\x7e\x03\xb4\x06\xb5\x06\xd6\x06\x00\x00\xbc\x06\x5d\x0c\x00\x00\x00\x00\x34\x2c\xe4\x23\x3c\x00\x8c\x3d\x1d\x00\x00\x00\xd2\x06\x97\x01\xdd\x06\x07\x4a\x00\x00\x00\x00\x58\x00\x00\x00\x34\x2c\xd4\x29\x05\x41\x0e\x07\x00\x00\xdf\x06\xca\x06\x00\x00\x9f\x04\x00\x00\x00\x00\x00\x00\x00\x00\x1c\x07\x5c\x00\x19\x06\x3c\x03\x00\x00\xe8\x06\x07\x4a\x9a\x36\x9a\x36\x52\x03\xa5\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x42\x40\x32\xcd\x06\x9a\x36\x00\x00\x40\x32\x53\x49\x6c\x2a\x6c\x2a\x1f\x07\x00\x00\x3b\x01\x00\x00\xc7\x06\x00\x00\xcb\x06\x00\x00\x00\x00\x77\x48\x77\x48\x00\x00\x00\x00\x77\x48\x8c\x31\xef\x06\xfd\x06\x00\x00\x00\x00\x35\x07\x00\x00\xf8\x03\xf8\x03\x00\x00\x00\x00\x00\x00\x43\x07\x00\x00\xe3\x06\x00\x00\xcc\x19\xff\x06\x80\x00\x80\x00\xff\x06\xec\x06\x00\x00\x00\x00\x00\x00\x1b\x07\x00\x00\x00\x00\x00\x00\x69\x02\x00\x00\x00\x00\x79\x01\x05\x07\x34\x2c\x80\x49\x57\x07\x00\x00\x0f\x07\x02\x07\x00\x00\x00\x00\x08\x07\x00\x00\x35\x42\x00\x00\x25\x07\x28\x07\x2e\x07\x2f\x07\xad\x49\x00\x00\x00\x00\x00\x00\x30\x07\x00\x00\x2a\x07\x13\x3a\x38\x07\x13\x3a\x07\x4a\x00\x00\x5c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x05\x13\x3a\x00\x00\x00\x00\x13\x3a\x1d\x07\x00\x00\xa8\x46\x00\x00\x55\x05\x00\x00\x3c\x07\x75\x07\x00\x00\x00\x00\x68\x05\x4f\x00\x05\x41\x3d\x07\x19\x37\x19\x37\x77\x07\x8d\x07\x46\x07\x13\x3a\x1d\x00\x3f\x07\x00\x00\x34\x4a\x00\x00\x55\x07\x00\x00\x00\x00\x50\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x3a\x00\x00\x40\x07\x13\x3a\x00\x00\x00\x00\x00\x00\x32\x07\x00\x00\xc4\x1c\x34\x2c\x00\x00\x00\x00\x98\x37\xad\x49\x4f\x00\x4f\x07\x05\x41\x98\x37\x98\x37\x3b\x04\x00\x00\x00\x00\x44\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\x00\x00\xcc\x2c\x00\x00\x00\x00\x64\x2d\x00\x00\x59\x00\x48\x07\x00\x00\x85\x05\x00\x00\x74\x27\x58\x07\x00\x00\x33\x07\x00\x00\x00\x00\x0c\x28\x00\x00\x00\x00\x00\x00\x64\x2d\x04\x2b\x64\x2d\x00\x00\x00\x00\xe4\x23\x8c\x45\x00\x00\x00\x00\x00\x00\x13\x3a\x00\x00\x00\x00\x6a\x07\x00\x00\x53\x07\x5e\x07\x36\x07\x13\x3a\x00\x00\x13\x3a\xdf\x48\x7e\x05\x00\x00\x5c\x07\x5c\x07\xad\x07\xd6\x03\xb0\x07\x00\x00\x30\x00\x30\x00\x00\x00\x60\x07\x45\x07\x00\x00\x47\x07\x00\x00\x00\x00\x61\x07\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x07\x00\x00\x78\x07\x00\x00\x00\x00\x00\x00\xb6\x07\x81\x07\x64\x2d\x9c\x2b\x00\x00\x00\x00\xa7\x07\x27\x04\xa4\x28\xa4\x28\x64\x2d\x68\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x98\x37\x98\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x07\x6d\x07\x93\x07\x00\x00\x94\x07\x00\x00\x82\x07\x05\x41\xc7\x07\xdd\x07\x00\x00\x65\x07\x00\x00\xe0\x07\x00\x00\x4c\x00\xe0\x07\x99\x05\x98\x37\x85\x04\x17\x38\x00\x00\x00\x00\x64\x2d\x00\x00\x64\x1a\x64\x1a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x1a\xfc\x1a\x00\x00\x00\x00\x00\x00\xe1\x07\xc7\x32\x00\x00\x05\x41\x13\x3a\xb2\x07\x96\x38\x00\x00\x00\x00\xad\x49\x00\x00\x00\x00\xaa\x05\xa2\x07\xda\x49\x00\x00\x40\x32\x09\x0b\x00\x00\x00\x00\xa0\x07\x00\x00\x8c\x07\x00\x00\x9d\x03\x00\x00\xf0\x07\xc0\x07\xc5\x07\xf8\x07\xa4\x07\x00\x00\xb0\x05\x00\x00\x00\x00\xb0\x05\xfe\x07\x00\x00\x00\x00\x64\x2d\xc8\x07\x00\x00\xfd\x07\xc4\x1c\xc4\x1c\x00\x00\x00\x00\x96\x38\x00\x00\xca\x07\x00\x00\xc6\x07\x00\x00\xca\x05\x00\x00\x0a\x08\x00\x00\x6a\x01\x00\x00\x00\x00\x0a\x08\x40\x02\x00\x00\xc7\x32\x00\x00\x00\x00\x8f\x01\x00\x00\xf9\x07\x64\x2d\x15\x39\x75\x02\x00\x00\x00\x00\x00\x00\xf0\x05\xf0\x05\x00\x00\x83\x03\xea\x07\x97\x07\x00\x00\x00\x00\x00\x00\x00\x00\x9e\x34\x00\x00\x25\x00\x00\x00\x08\x08\x00\x00\x1e\x08\x00\x00\x05\x41\x00\x00\x00\x00\x13\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x64\x2d\x64\x2d\x64\x2d\x00\x00\x00\x00\x00\x00\xa9\x07\x26\x08\x00\x00\x00\x00\x00\x00\x00\x00\xa8\x01\x00\x00\x7b\x00\x62\x42\xc4\x02\xda\x05\xd1\x07\x00\x00\xbc\x43\xd6\x03\x00\x00\x00\x00\x00\x00\xda\x05\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x03\xc9\x07\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x03\xb8\x03\x61\x04\xa9\x0a\xd6\x03\x00\x00\x00\x00\x00\x00\x43\x00\xd4\x07\xcb\x07\x8f\x42\x02\x08\x9d\x03\x00\x00\x64\x2d\xf4\x07\x00\x00\x00\x00\x15\x08\x00\x00\xee\x07\x00\x00\x00\x00\x0b\x3e\x34\x4a\xfa\x07\xd6\x07\xe5\x07\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\xdc\x07\x00\x00\x05\x08\xe7\x07\xf5\x07\x00\x00\x94\x1b\x00\x00\x6d\x04\x8a\x3e\x05\x41\x37\x18\x05\x41\x00\x00\x00\x00\x00\x00\x2c\x1c\x8a\x3e\x00\x00\x00\x00\x16\x08\x00\x00\x92\x3a\x11\x3b\xc7\x32\x90\x3b\x00\x00\xf0\x01\xd6\x02\xda\x49\x90\x3b\x00\x00\x58\x08\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\x00\x08\x4b\x00\x9d\x03\xf2\x07\x07\x08\x00\x00\x00\x00\x00\x00\xc7\x32\x00\x00\xff\x01\x00\x00\x59\x00\xf5\x02\x06\x08\x09\x3f\x00\x00\x00\x00\x11\x08\x94\x39\x8e\x04\x00\x00\x00\x00\x90\x3b\x0f\x3c\x00\x00\x00\x00\x7e\x03\x94\x39\xf0\x05\x00\x00\x00\x00\x94\x39\xe8\x07\x14\x08\x12\x08\x00\x00\x8e\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x05\x41\x64\x2d\xf7\x07\x00\x00\x26\x02\x9d\x03\x00\x00\x9d\x03\x00\x00\x9d\x03\x00\x00\x00\x00\x0d\x08\x0e\x08\x13\x08\x19\x08\x00\x00\x98\x02\x00\x00\x00\x00\x00\x00\x5d\x44\x0b\x08\x00\x00\x00\x00\xd6\x03\x1c\x08\x0c\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7b\x03\x00\x00\x7e\x08\xc7\x02\x00\x00\x3d\x00\x26\x02\x21\x08\x33\x08\x00\x00\x00\x00\x00\x00\x88\x3f\x00\x00\x04\x08\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x08\x3b\x08\x21\x33\x00\x00\x00\x00\x34\x4a\x00\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x07\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x08\xd6\x03\x00\x00\x00\x00\x2a\x08\xd6\x03\x00\x00\x76\x08\x89\x08\x47\x08\xc7\x32\x00\x00\x86\x40\x00\x00\x00\x00\x7d\x08\x2e\x08\x50\x09\x9d\x03\x00\x00\x9d\x03\x9d\x03\x00\x00\x9d\x03\x5d\x44\x00\x00\x00\x00\xf5\x43\x00\x00\x00\x00\x00\x00\x00\x00\x24\x08\x4d\x08\x00\x00\x9d\x03\x82\x08\xe6\x05\x00\x00\x00\x00\x95\x08\x35\x08\x00\x00\x00\x00\x00\x00\x00\x00\xe6\x05\x2c\x08\x9d\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
2356
2357happyGotoOffsets :: HappyAddr
2358happyGotoOffsets = HappyA# "\x05\x00\xfe\xff\x72\x08\x01\x4e\x4a\x01\x95\x52\xbd\x51\xd0\xff\x49\x4e\x01\x00\x81\x12\x71\x00\x07\x00\x92\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x04\x00\x00\x00\x00\x00\x00\x90\x02\x00\x00\x00\x00\x00\x00\xba\x02\x00\x00\x00\x00\xf6\x04\x02\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfe\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd1\x04\x2c\x00\x9e\x12\x34\x0e\x14\x0e\x86\x02\x35\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdd\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x04\x73\x07\x24\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x0b\x00\x00\x00\x00\x25\x53\x6d\x53\xfc\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb5\x53\xb7\x07\x55\x50\x40\x05\xbc\x07\xdd\x35\xbd\x07\x5c\x36\x00\x00\x00\x00\x00\x00\x24\x13\xdb\x36\x10\x14\x5a\x37\x01\x4a\x79\x45\x5f\x46\x50\x3c\x4b\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x53\x95\x5b\xbb\x12\xda\x07\x45\x54\x00\x00\x8d\x54\x69\x04\x75\x08\x00\x00\x00\x00\xf0\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x05\xa1\x01\x06\x05\x31\x05\x37\x05\x3a\x03\xf7\x06\x47\x02\xec\x45\x00\x00\x00\x00\xd9\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x01\x00\x00\x00\x00\x00\x00\x00\x00\x57\x03\x00\x00\x00\x00\xfd\x05\x6c\x08\x00\x00\x1a\x01\x31\x08\x94\x00\xdb\x05\x81\x02\x1d\x01\xd1\x05\xd7\x38\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x08\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x01\x00\x00\x21\x02\x00\x00\x9b\x02\x86\x07\x87\x07\x88\x07\x83\x08\x00\x00\x94\x04\x56\x39\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd5\x39\xb4\x07\xe2\x04\x00\x00\x00\x00\x42\x08\x00\x00\x00\x00\x00\x00\x45\x08\x00\x00\x00\x00\xdd\x05\x00\x00\xc0\xff\x00\x00\xb9\x00\xfe\x02\x00\x00\x46\x08\x48\x08\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x04\x44\x16\x7d\x03\xe9\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x16\xa9\x10\x78\x16\x28\x08\x00\x00\x00\x00\xb3\x04\x00\x00\x60\x34\x00\x00\x00\x00\x56\x08\x24\x03\xb1\x07\x6e\x08\x00\x00\x00\x00\x00\x00\xdd\x0c\x8c\xff\x00\x00\x00\x00\xdd\x5b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x4a\x4b\x4b\x00\x00\x10\x14\x00\x00\x00\x00\xe6\x03\x00\x00\x4c\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x05\x00\x00\x03\x04\x00\x00\x00\x00\x06\x04\x0b\x0f\x23\x04\x00\x00\x00\x00\x08\x03\x50\x03\xb7\xff\x7c\x08\xeb\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x01\x9a\x07\x00\x00\x00\x00\x00\x00\x0d\x00\x11\x00\x00\x00\x12\x0e\x00\x00\x00\x00\x00\x00\x0c\x04\xfb\x07\x00\x00\x8c\xff\x00\x00\x00\x00\x00\x00\x6f\x4a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x3a\x00\x00\x00\x00\x7b\x09\xf1\x07\xd3\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x91\x4e\xd9\x4e\x00\x00\x00\x00\x00\x00\x10\x08\x7f\xff\x00\x00\x00\x00\x26\x4f\x72\x05\x00\x00\x00\x00\x52\x3b\xd5\x54\x4f\x02\x00\x00\x2d\x05\x00\x00\x00\x00\xb1\x5c\x8c\x10\x1d\x55\x65\x55\xad\x55\xf5\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\x10\xee\x0d\x75\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x02\x00\x00\xac\x00\x00\x00\xb1\x04\x00\x00\x00\x00\x4a\x08\x55\x01\x00\x00\x8a\xff\xdd\x16\x00\x00\x45\x15\x62\x15\x50\x13\x00\x00\x00\x00\x16\x00\xb3\x07\x00\x00\xda\x01\x00\x00\xa6\x07\xaf\x07\xca\x08\x00\x00\x00\x00\xd0\x08\x00\x00\x00\x00\xb9\x08\x00\x00\x00\x00\x00\x00\x00\x00\xe7\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7f\x15\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x03\x00\x00\x00\x00\x00\x00\xe3\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x11\x00\x00\x00\x00\x00\x00\x95\x11\xb2\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x08\x03\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x56\x85\x56\xc4\x07\x00\x00\x00\x00\xcd\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x73\x4f\xb7\x49\x5e\x35\x00\x00\xb9\x4b\x00\x00\x15\x57\x71\x4d\x27\x4c\x00\x00\x8f\xff\x00\x00\x00\x00\x00\x00\xdd\x4a\x00\x00\x00\x00\xc4\x5c\x00\x00\x00\x00\x00\x00\x00\x00\x92\x01\xcd\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x58\x02\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x07\x00\x00\x1e\x18\x90\x01\x00\x00\xce\x07\x00\x00\x00\x00\x78\x01\x00\x00\x00\x00\x00\x00\xd0\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x06\xa0\x04\x00\x00\x00\x00\xb8\x02\x5c\x02\x00\x00\x00\x00\x25\x05\x00\x00\x00\x00\x12\x0e\x00\x00\x00\x00\xb1\x5c\x95\x4c\x00\x00\x0f\x08\xb0\xff\x00\x00\x00\x00\xc1\x07\x00\x00\x99\x01\x00\x00\x00\x00\x06\x00\x00\x00\x5d\x57\xc0\x4f\xf7\x16\x8e\x08\x1e\x04\xa4\x08\x00\x00\x00\x00\xb6\x08\x00\x00\x00\x00\x00\x00\x00\x00\x93\x08\x77\x05\x4a\x05\xab\x08\x00\x00\x00\x00\x9d\x01\x32\x0c\x4f\x0c\x02\x04\xc1\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xed\xff\xdc\x02\xd7\x07\xbe\x08\x00\x00\xd4\xff\x51\x00\x05\x52\x4d\x52\x8f\x08\x00\x00\x00\x00\x00\x00\x91\x08\x00\x00\x8a\x08\x00\x00\x00\x00\xc0\x00\xd3\x07\x00\x00\x00\x00\xdc\x00\xd1\x3b\x00\x00\x00\x00\x00\x00\x00\x00\xd2\x08\x00\x00\xf2\x08\xf3\x08\x00\x00\x00\x00\x00\x00\xe8\x02\x00\x00\xe0\x08\x00\x00\x92\x01\xed\x08\x94\x08\x9b\x08\xef\x08\xde\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x5c\xe5\xff\xb5\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7f\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x13\xd5\x08\x8a\x13\x56\x00\x00\x00\xbb\x08\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x08\xa0\x0f\x00\x00\x00\x00\xa7\x13\x00\x00\x00\x00\x4b\x02\x00\x00\xbc\x08\x00\x00\x00\x00\xb7\x08\x00\x00\x00\x00\xf2\x05\x9c\x08\x11\x17\x00\x00\x28\x0b\x45\x0b\x7f\x08\x33\x05\x00\x00\x3c\x14\xbf\xff\x00\x00\x00\x00\xe4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x0f\x00\x00\x00\x00\xda\x0f\x00\x00\x00\x00\x00\x00\x6b\x05\x00\x00\xcf\x06\xa5\x57\x00\x00\x00\x00\x1c\x09\xa7\x03\x9e\x08\x00\x00\x24\x17\x6c\x0c\x02\x0d\x0e\x03\x00\x00\x00\x00\xfd\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xed\x57\x00\x00\x00\x00\x35\x58\x00\x00\x01\x08\x00\x00\x00\x00\xbd\x04\x00\x00\x0d\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x50\x00\x00\x00\x00\x00\x00\x7d\x58\x2d\x51\xc5\x58\x00\x00\x00\x00\x03\x4d\xf6\x01\x00\x00\x00\x00\x00\x00\xcf\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x03\x14\x16\x00\x00\x59\x14\x22\x00\x24\x09\x00\x00\x17\x09\x18\x09\x00\x00\x15\x00\x00\x00\x00\x00\xfb\xff\xfd\xff\x00\x00\x00\x00\x71\x03\x00\x00\xa1\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x73\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x08\x52\x08\x0d\x59\x75\x51\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x4d\xe5\x50\x55\x59\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x0d\x3c\x0d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x17\x9a\x08\x6a\x05\x00\x00\x84\x00\x00\x00\x8d\x08\x00\x00\x0c\x00\x6d\x05\x00\x00\x59\x0d\x00\x00\x62\x0b\x00\x00\x00\x00\x9d\x59\x00\x00\xeb\x03\x33\x04\x00\x00\x9f\x08\xc4\x05\x00\x00\x00\x00\x00\x00\x29\x02\x71\x02\x00\x00\x00\x00\x00\x00\xf8\x08\x1b\x00\x00\x00\xbd\x17\x76\x14\x00\x00\x5e\x09\x00\x00\x00\x00\x64\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe8\xff\x00\x00\xeb\x02\x12\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2e\x09\x00\x00\x00\x00\x2f\x09\x14\x09\x00\x00\x00\x00\xe5\x59\x00\x00\x00\x00\x00\x00\xcd\x05\x4e\x06\x00\x00\x00\x00\x84\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x00\x01\x09\x00\x00\x2b\x08\x00\x00\x00\x00\x03\x09\x00\x00\x00\x00\x4b\x02\x00\x00\x00\x00\x2d\x08\x00\x00\x09\x09\x6d\x5c\x99\x06\x00\x00\x00\x00\x00\x00\x00\x00\x77\x02\xb1\x02\x00\x00\xdc\xff\x19\x09\x29\x08\x00\x00\x00\x00\x00\x00\x00\x00\x7f\x0b\x00\x00\x42\x03\x00\x00\xaf\x08\x00\x00\x70\x05\x00\x00\x37\x0a\x00\x00\x00\x00\xf7\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2d\x5a\x75\x5a\xbd\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x32\x08\x00\x00\x00\x00\x26\x00\x00\x00\x43\x09\x00\x00\x00\x00\x55\x00\xe3\xff\x00\x00\x00\x00\x00\x00\x4e\x09\x00\x00\xe6\x02\xe7\x02\x00\x00\x27\x00\x3d\x09\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x08\x53\x04\xdb\x02\x84\x04\x2b\x00\x00\x00\x00\x00\x00\x00\x03\x00\x64\x09\x00\x00\x29\x00\x3f\x09\x4b\x08\x00\x00\x05\x5b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x0a\x34\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x05\x00\x00\x25\x09\x18\x07\xd7\x17\x12\x0e\xea\x17\x00\x00\x00\x00\x00\x00\xca\x04\x52\x07\x00\x00\x00\x00\x27\x09\x00\x00\x24\x05\x31\x06\x46\x00\x93\x14\x00\x00\x62\x08\x00\x00\x20\x00\x31\x16\x00\x00\x5c\x09\x00\x00\x3a\x02\x5f\x02\x00\x00\x64\x08\x00\x00\x44\x06\x66\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x02\x00\x00\x65\x08\x00\x00\x68\x08\x00\x00\x00\x00\x22\x08\x00\x00\x00\x00\x46\x09\xca\x09\x48\x09\x00\x00\x00\x00\x28\x15\x64\x12\x00\x00\x00\x00\x2d\x01\x24\x0a\x39\x04\x00\x00\x00\x00\x15\x0c\x95\x03\x00\x00\x00\x00\x00\x00\x91\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x04\x18\x4d\x5b\x00\x00\x00\x00\x86\x09\x78\x08\x00\x00\xff\xff\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x01\x00\x00\x00\x00\x00\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x09\x88\x09\x00\x00\x00\x00\x00\x00\x00\x00\x7e\x0a\x00\x00\x98\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x0e\x00\x00\x00\x00\x52\x01\x00\x00\x00\x00\xc9\xff\x00\x00\x00\x00\x76\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x19\x00\x00\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x06\x09\x73\x05\x00\x00\x1c\x00\x00\x00\x91\x0a\x00\x00\x00\x00\x00\x00\x8d\x09\x1f\x00\x7a\x08\x00\x00\x02\x00\x8b\x08\x00\x00\xf5\xff\x5f\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8c\x08\x00\x00\x99\x09\x00\x00\x00\x00\x76\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x09\x00\x00\x90\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
2359
2360happyAdjustOffset :: Happy_GHC_Exts.Int# -> Happy_GHC_Exts.Int#
2361happyAdjustOffset off = off
2362
2363happyDefActions :: HappyAddr
2364happyDefActions = HappyA# "\xbe\xff\xbf\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x79\xfd\x00\x00\x00\x00\xbd\xff\xbe\xff\x00\x00\xf2\xff\x09\xfd\x06\xfd\x03\xfd\xf3\xfc\xf1\xfc\xf2\xfc\xff\xfc\xf0\xfc\xef\xfc\xee\xfc\x01\xfd\x00\xfd\x02\xfd\xfe\xfc\xfd\xfc\xed\xfc\xec\xfc\xeb\xfc\xea\xfc\xe9\xfc\xe8\xfc\xe7\xfc\xe6\xfc\xe5\xfc\xe4\xfc\xe2\xfc\xe3\xfc\x00\x00\x04\xfd\x05\xfd\x00\x00\x89\xff\x00\x00\xaf\xff\xc0\xff\x89\xff\xc1\xfc\x00\x00\x00\x00\x00\x00\x7a\xfe\x00\x00\x9e\xfe\x00\x00\x97\xfe\x90\xfe\x83\xfe\x82\xfe\x80\xfe\x6e\xfe\x6d\xfe\x00\x00\x79\xfe\x40\xfd\x7e\xfe\x3b\xfd\x31\xfd\x34\xfd\x2b\xfd\x78\xfe\x7d\xfe\x12\xfd\x0f\xfd\x65\xfe\x5a\xfe\x0d\xfd\x0c\xfd\x0e\xfd\x00\x00\x00\x00\x28\xfd\x24\xfd\x27\xfd\x26\xfd\x77\xfe\x25\xfd\x00\x00\xbd\xfc\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\xfd\x2e\xfd\x29\xfd\x2a\xfd\x32\xfd\x2c\xfd\x2d\xfd\x67\xfd\x66\xfe\x67\xfe\xc8\xfd\x00\x00\x0e\xfe\x0d\xfe\x00\x00\xf1\xff\x56\xfd\x49\xfd\x55\xfd\xef\xff\xf0\xff\x16\xfd\xfb\xfc\xfc\xfc\xf7\xfc\xf4\xfc\x54\xfd\xde\xfc\x45\xfd\xdb\xfc\xd8\xfc\xed\xff\xf6\xfc\xe1\xfc\xdf\xfc\xe0\xfc\x00\x00\x00\x00\x00\x00\x00\x00\xdc\xfc\xf5\xfc\xd9\xfc\xdd\xfc\xf8\xfc\xda\xfc\xcc\xfd\x74\xfd\x07\xfe\xfe\xfd\x06\xfe\x00\x00\x00\x00\xff\xfd\xf4\xfd\xe8\xfd\xe6\xfd\xd8\xfd\xd7\xfd\x00\x00\x00\x00\x7a\xfd\x77\xfd\xe3\xfd\xe2\xfd\xe4\xfd\xe5\xfd\xe1\xfd\xd9\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x66\xfd\xd7\xfc\xd6\xfc\xe0\xfd\xdf\xfd\xd3\xfc\xd2\xfc\xd5\xfc\xd4\xfc\xd1\xfc\xd0\xfc\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\xfd\x00\x00\xd2\xfd\x76\xff\x1b\xfe\x00\x00\x00\x00\x04\xfe\x00\x00\x06\xfd\x74\xff\x73\xff\x72\xff\x00\x00\x00\x00\x12\xfe\x12\xfe\x12\xfe\x00\x00\x64\xfd\x00\x00\x00\x00\x88\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x6c\xff\x6b\xff\x6a\xff\x69\xff\x12\xff\x68\xff\x67\xff\x27\xfe\x61\xff\x26\xfe\x2f\xfe\x60\xff\x2a\xfe\x5f\xff\x2e\xfe\x2d\xfe\x2c\xfe\x2b\xfe\x00\x00\x26\xff\x00\x00\x44\xff\x4d\xff\x25\xff\x00\x00\x00\x00\x00\x00\xd9\xfe\xc3\xfe\xc8\xfe\x00\x00\x00\x00\xc5\xfc\xc4\xfc\xc3\xfc\xc2\xfc\x00\x00\x78\xfd\x00\x00\x83\xff\x00\x00\x00\x00\x00\x00\x00\x00\x89\xff\xc1\xff\x89\xff\x00\x00\x86\xff\x00\x00\x00\x00\x00\x00\x81\xff\x00\x00\x00\x00\x00\x00\x59\xfd\x50\xfd\x5a\xfd\x0b\xfd\x52\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xc9\xfe\x00\x00\x5c\xfd\x00\x00\xc4\xfe\x00\x00\x00\x00\xda\xfe\xd7\xfe\x00\x00\x4f\xfd\x00\x00\x00\x00\x00\x00\x65\xff\x00\x00\x00\x00\x00\x00\x00\x00\x90\xfe\x40\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x45\xff\x00\x00\x46\xff\x48\xff\x47\xff\x00\x00\x60\xfe\x00\x00\x57\xfe\x00\x00\x19\xff\x00\x00\x1c\xfd\x00\x00\x1b\xfd\x1d\xfd\x00\x00\x00\x00\x00\x00\x12\xff\x00\x00\x87\xfd\xbd\xfd\x07\xfe\x00\x00\x00\x00\x19\xfd\x00\x00\x18\xfd\x1a\xfd\x14\xfd\xf9\xfc\x00\x00\xfa\xfc\x45\xfd\x00\x00\x00\x00\xc6\xfc\xf6\xfc\x4d\xfd\xca\xfc\x00\x00\x4f\xfd\xaa\xfe\x00\x00\x65\xfd\x63\xfd\x61\xfd\x60\xfd\x5d\xfd\x00\x00\x00\x00\x00\x00\x11\xfe\x00\x00\x00\x00\x00\x00\x00\x00\xe1\xfe\x00\x00\xe4\xfe\xe4\xfe\x00\x00\x00\x00\x00\x00\x75\xff\xd3\xfd\x43\xfd\xd4\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\xff\x6d\xff\x00\x00\x00\x00\x00\x00\xd5\xfd\xd6\xfd\x00\x00\xc3\xfd\xe5\xfd\x00\x00\x00\x00\xf9\xfc\xfa\xfc\x00\x00\x4b\xfd\x00\x00\xb1\xfd\x00\x00\xb0\xfd\x48\xfd\x85\xfd\x02\xfe\xf2\xfd\x84\xfd\x81\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf5\xfd\x76\xfd\x7b\xfd\x7b\xfd\x00\x00\xea\xfd\x73\xfd\xfb\xfd\x00\x00\xed\xfd\x8c\xfd\x00\x00\x00\x00\xeb\xfd\x00\x00\x00\x00\x00\x00\x71\xfd\xf7\xfd\x00\x00\x01\xfe\xfd\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6c\xfe\x58\xfd\x57\xfd\x7c\xfe\x7b\xfe\x69\xfe\x1f\xfd\x60\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x5f\xfe\x00\x00\x00\x00\x00\x00\x73\xfe\x00\x00\x34\xfd\x00\x00\x00\x00\x75\xfe\x00\x00\x3c\xfd\x00\x00\x3d\xfe\x3b\xfe\xbe\xfc\x00\x00\x7f\xfe\x00\x00\xa1\xfe\xa2\xfe\x00\x00\x5a\xfe\x59\xfe\x00\x00\x00\x00\x81\xfe\x00\x00\x00\x00\x00\x00\x00\x00\xe7\xff\x00\x00\x00\x00\xac\xff\x86\xff\xab\xff\x00\x00\x00\x00\xba\xff\xcd\xfc\xcc\xfc\xba\xff\xaa\xff\xa8\xff\xa9\xff\x8a\xff\xeb\xff\xce\xfc\xcf\xfc\xe8\xff\x00\x00\xd7\xff\xdb\xff\xd8\xff\xda\xff\xd9\xff\xdc\xff\xea\xff\x50\xfe\x9d\xfe\x99\xfe\x8f\xfe\x98\xfe\x00\x00\x5b\xfe\x00\x00\x9f\xfe\xa0\xfe\x00\x00\xa5\xfe\x00\x00\x00\x00\x76\xfe\x70\xfe\x00\x00\x3d\xfd\x3f\xfd\xcb\xfc\x3a\xfd\x6f\xfe\x00\x00\x3e\xfd\x71\xfe\x72\xfe\x00\x00\x00\x00\x11\xfd\x33\xfd\x00\x00\x00\x00\x00\x00\x28\xfd\x27\xfd\x26\xfd\x77\xfe\x25\xfd\x29\xfd\x2a\xfd\x2d\xfd\x5f\xfe\x00\x00\x61\xfe\xc7\xfd\xec\xff\xee\xff\x4c\xfd\x53\xfd\x07\xfd\x4a\xfd\x44\xfd\x15\xfd\x08\xfe\x09\xfe\x0a\xfe\x0b\xfe\x0c\xfe\xa8\xfe\x05\xfe\xf6\xfd\x00\x00\x72\xfd\x6f\xfd\x6c\xfd\x6e\xfd\x75\xfd\xf3\xfd\x00\x00\x00\x00\x00\x00\x9d\xfd\x9b\xfd\x8d\xfd\x8a\xfd\x00\x00\xfc\xfd\x00\x00\x00\x00\x00\x00\x7c\xfd\x00\x00\x00\x00\xfa\xfd\xf9\xfd\x00\x00\x83\xfd\xef\xfd\x00\x00\x00\x00\x81\xfd\x00\x00\x00\x00\xda\xfd\xaf\xfd\x00\x00\x00\x00\x08\xfd\xb3\xfd\xb7\xfd\xdb\xfd\xb9\xfd\xb2\xfd\xb8\xfd\xdc\xfd\x00\x00\xd1\xfd\xce\xfd\xcf\xfd\xbe\xfd\xbf\xfd\x00\x00\x00\x00\xcd\xfd\xd0\xfd\xc5\xfd\x41\xfd\x00\x00\x42\xfd\x1c\xfe\x22\xfd\x70\xff\x23\xfd\x47\xfd\x21\xfd\x20\xfd\x00\x00\x1e\xfe\xa7\xfe\x00\x00\x93\xfe\x8e\xfe\x00\x00\x00\x00\x5a\xfe\x00\x00\x00\x00\x25\xfe\xe5\xfe\xac\xfe\x24\xfe\xca\xfd\xc9\xfd\x00\x00\x69\xfd\xe3\xfd\x00\x00\x00\x00\x00\x00\x64\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc8\xfc\xc7\xfc\x08\xfd\xbb\xfd\xdd\xfd\xde\xfd\xbc\xfd\x00\x00\x00\x00\x00\x00\x24\xff\xab\xfe\x00\x00\x8e\xfe\x00\x00\x5a\xfe\x03\xfe\x28\xfe\xdd\xfe\x20\xfe\x00\x00\x00\x00\x00\x00\xf2\xfe\x52\xfe\x22\xff\x00\x00\x49\xff\x4d\xff\x4e\xff\x4f\xff\x51\xff\x50\xff\xe8\xfe\x0f\xff\x00\x00\x20\xff\x54\xff\x00\x00\x5a\xfe\x00\x00\x00\x00\x00\x00\x00\x00\xb6\xfe\xb5\xfe\xb4\xfe\xb3\xfe\xb2\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x06\xff\x03\xff\x00\x00\x00\x00\x00\x00\xd0\xfe\xd6\xfe\x00\x00\x62\xff\xdb\xfe\xc2\xfe\xbd\xfe\xc1\xfe\x64\xff\xc5\xfe\x00\x00\xc7\xfe\x63\xff\xca\xfe\x00\x00\x00\x00\x00\x00\x29\xfe\x84\xff\x7d\xff\x82\xff\xba\xff\xba\xff\xb6\xff\xb5\xff\xb2\xff\x6d\xff\xb7\xff\x88\xff\xb3\xff\xb4\xff\xa6\xff\x00\x00\x00\x00\xa6\xff\x7f\xff\x7e\xff\xbc\xfe\xba\xfe\x00\x00\xcb\xfe\x5b\xfd\xc6\xfe\x00\x00\xbe\xfe\xdc\xfe\x00\x00\x00\x00\x00\x00\xce\xfe\x08\xff\x09\xff\x00\x00\x01\xff\x02\xff\xfd\xfe\x00\x00\x05\xff\x00\x00\xb8\xfe\x00\x00\xb0\xfe\xaf\xfe\xb1\xfe\x00\x00\xb7\xfe\x57\xff\x58\xff\x9c\xfe\x5d\xff\x00\x00\x00\x00\x43\xff\x00\x00\x00\x00\x10\xff\x0e\xff\x0d\xff\x0a\xff\x0b\xff\x55\xff\x00\x00\x00\x00\x66\xff\x59\xff\x00\x00\x56\xfe\x54\xfe\x00\x00\x5e\xff\x00\x00\x1a\xff\x00\x00\xdd\xfe\x22\xfe\x21\xfe\x00\x00\x00\x00\x00\x00\x8d\xfe\x00\x00\x00\x00\x4d\xfe\x39\xfe\x00\x00\x00\x00\x24\xff\x00\x00\x15\xff\x5a\xfe\x13\xff\x00\x00\xba\xfd\xb6\xfd\xc9\xfc\x17\xfd\x13\xfd\x4e\xfd\xa9\xfe\x1a\xfe\x62\xfd\x5f\xfd\x51\xfd\x5e\xfd\x17\xfe\x00\x00\x10\xfe\x00\x00\x00\x00\x14\xfe\x19\xfe\xe0\xfe\x6a\xfd\xe3\xfe\xe6\xfe\x00\x00\xdf\xfe\xe2\xfe\x00\x00\x00\x00\x00\x00\x8c\xfe\x00\x00\x00\x00\x00\x00\x00\x00\xc1\xfd\xc0\xfd\x6f\xff\xc2\xfd\xc4\xfd\xcb\xfd\xb5\xfd\xb4\xfd\xbd\xfd\xa9\xfd\xab\xfd\xa8\xfd\xa6\xfd\xa3\xfd\xa2\xfd\x00\x00\xad\xfd\xaa\xfd\x00\x00\x82\xfd\x00\x00\x96\xfd\x92\xfd\x00\x00\x97\xfd\x00\x00\x00\x00\x98\xfd\x00\x00\x00\xfe\x80\xfd\x7d\xfd\x7f\xfd\xe9\xfd\xf0\xfd\x00\x00\x00\x00\x00\x00\x8b\xfd\xec\xfd\x00\x00\x00\x00\xe7\xfd\x6a\xfe\x0a\xfd\x00\x00\x1e\xfd\x5e\xfe\x5d\xfe\x5c\xfe\x00\x00\x00\x00\xbf\xfc\x00\x00\x9a\xfe\x00\x00\x00\x00\x00\x00\xe9\xff\xa6\xff\xa6\xff\x00\x00\x9f\xff\x00\x00\xe6\xff\xbf\xff\xbf\xff\xd6\xff\x00\x00\xbf\xfc\xc0\xfc\xbd\xfc\x68\xfe\x74\xfe\x00\x00\x70\xfd\x6d\xfd\x89\xfd\x9c\xfd\xfb\xfd\x7e\xfd\x00\x00\x9a\xfd\x95\xfd\x91\xfd\xdd\xfe\x8e\xfd\x00\x00\x93\xfd\x99\xfd\xf1\xfd\xa1\xfd\xe8\xfc\x00\x00\x00\x00\xae\xfd\x6e\xff\x8b\xff\x71\xff\x95\xfe\x8b\xfe\x94\xfe\x00\x00\x00\x00\xa6\xfe\x1d\xfe\x68\xfd\xe7\xfe\x6b\xfd\x00\x00\xa4\xfe\x00\x00\x0f\xfe\x00\x00\x14\xff\x00\x00\x00\x00\x4d\xfe\x39\xfe\x23\xff\xbd\xfc\x5b\xff\x38\xfe\x36\xfe\x00\x00\x39\xfe\x00\x00\x00\x00\x94\xfe\x00\x00\xde\xfe\x23\xfe\x00\x00\xf3\xfe\xf6\xfe\xf6\xfe\x51\xfe\x52\xfe\x52\xfe\x21\xff\x11\xff\xe9\xfe\xec\xfe\xec\xfe\x0c\xff\x1e\xff\x1f\xff\x3e\xff\x00\x00\x33\xff\x00\x00\x00\x00\x00\x00\x00\x00\xb9\xfe\x46\xfd\x00\x00\x04\xff\x07\xff\x00\x00\x00\x00\xce\xfe\xcd\xfe\x00\x00\x00\x00\xd5\xfe\xd3\xfe\x00\x00\xc0\xfe\x00\x00\xbb\xfe\x00\x00\x80\xff\x00\x00\x00\x00\x00\x00\x00\x00\x87\xff\x8c\xff\x00\x00\xbc\xff\xbb\xff\x00\x00\x7d\xff\xbf\xfe\xd4\xfe\x00\x00\x00\x00\xcf\xfe\xd1\xfe\xe4\xfe\xe4\xfe\x00\xff\xad\xfe\x00\x00\x9b\xfe\x00\x00\x42\xff\x00\x00\x5c\xff\x00\x00\xf1\xfe\x2b\xff\xed\xfe\x00\x00\xf0\xfe\x26\xff\x2b\xff\x00\x00\x55\xfe\x53\xfe\xfc\xfe\xf7\xfe\x00\x00\xfb\xfe\x2d\xff\x00\x00\x00\x00\x00\x00\x1f\xfe\x96\xfe\x8a\xfe\x4a\xfe\x4a\xfe\x5a\xff\x00\x00\x35\xfe\x30\xfd\x32\xfe\x4a\xff\x4c\xff\x4b\xff\x00\x00\x37\xfe\x46\xfe\x44\xfe\x40\xfe\x53\xff\x39\xfe\x16\xff\x00\x00\x15\xfe\x16\xfe\x00\x00\x89\xfe\xac\xfd\xa5\xfd\xa4\xfd\xa7\xfd\x00\x00\x00\x00\x00\x00\x94\xfd\x8f\xfd\x90\xfd\x00\x00\x00\x00\x6b\xfe\x3c\xfe\x3a\xfe\x58\xfe\x00\x00\xca\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\xff\xa1\xff\x9f\xff\x9c\xff\x9d\xff\x9e\xff\x00\x00\xb0\xff\x89\xff\x89\xff\xa0\xff\x9f\xff\x98\xff\x90\xff\x8d\xff\x39\xfd\x8e\xff\x00\x00\x00\x00\x00\x00\x00\x00\x9f\xff\xa7\xff\xb1\xff\xce\xff\xcb\xff\xd5\xff\xe5\xff\xe2\xfc\x83\xff\x00\x00\xcd\xff\x00\x00\x00\x00\xa0\xfd\x9f\xfd\x00\x00\xa3\xfe\x00\x00\x17\xff\x52\xff\x00\x00\x5a\xfe\x00\x00\x63\xfe\x00\x00\x31\xfe\x2f\xfd\x33\xfe\x34\xfe\x00\x00\x4b\xfe\x48\xfe\x00\x00\x00\x00\x00\x00\xf5\xfe\xf8\xfe\x2f\xff\x1d\xff\x00\x00\x00\x00\x00\x00\x00\x00\x2c\xff\xf4\xfe\xeb\xfe\xee\xfe\x00\x00\x2a\xff\xea\xfe\x12\xff\x3d\xff\x35\xff\x35\xff\x00\x00\x00\x00\xae\xfe\x00\x00\x00\x00\xce\xfe\x00\x00\xd8\xfe\x7b\xff\xc3\xff\x89\xff\x89\xff\xc2\xff\x00\x00\x00\x00\x79\xff\x00\x00\x00\x00\x00\x00\xff\xfe\xfe\xfe\x34\xff\x41\xff\x3f\xff\x00\x00\x36\xff\x00\x00\x00\x00\x00\x00\x00\x00\x29\xff\xef\xfe\x22\xff\x00\x00\x1d\xff\x2e\xff\x31\xff\x00\x00\x00\x00\xf9\xfe\x4f\xfe\x00\x00\x00\x00\x4a\xfe\x4e\xfe\x30\xfe\x00\x00\xbf\xfc\x00\x00\x00\x00\x91\xfe\x3f\xfe\x87\xfe\x85\xfe\x42\xfe\x84\xfe\x00\x00\x00\x00\x00\x00\xee\xfd\xc6\xff\x00\x00\xc4\xff\x00\x00\xc5\xff\x00\x00\xcc\xff\xa5\xff\x00\x00\x00\x00\x00\x00\x00\x00\x99\xff\x00\x00\x8f\xff\x9a\xff\x9b\xff\x96\xff\xa2\xff\xad\xff\xae\xff\x9f\xff\x00\x00\x95\xff\x93\xff\x92\xff\x91\xff\x38\xfd\x37\xfd\x35\xfd\x36\xfd\x00\x00\xd1\xff\xcf\xff\x00\x00\xe1\xff\x00\x00\xc7\xff\xa6\xff\x00\x00\x9e\xfd\x18\xff\x86\xfe\x00\x00\x41\xfe\xbd\xfc\x62\xfe\x4c\xfe\x47\xfe\x49\xfe\x00\x00\x78\xfe\x00\x00\x1c\xff\x30\xff\x00\x00\xfa\xfe\x32\xff\x24\xff\x3a\xff\x3c\xff\x37\xff\x39\xff\x3b\xff\x40\xff\xd2\xfe\xcc\xfe\x7c\xff\x85\xff\x7a\xff\x00\x00\x9f\xff\xb9\xff\xb8\xff\x00\x00\x9f\xff\x38\xff\x4d\xfe\x39\xfe\x78\xfe\x00\x00\x45\xfe\x3f\xfe\x43\xfe\xf8\xfd\x00\x00\xa6\xff\x00\x00\x00\x00\xe4\xff\xe2\xff\x00\x00\xd4\xff\xd2\xff\x00\x00\x97\xff\xa3\xff\xa1\xff\x94\xff\xd3\xff\xd0\xff\xe3\xff\x00\x00\x00\x00\xe0\xff\x00\x00\x00\x00\x00\x00\x1b\xff\x28\xff\x39\xfe\x00\x00\x78\xff\x77\xff\x27\xff\xc8\xff\x00\x00\x00\x00\x00\x00\xdf\xff\xdd\xff\xde\xff\xc9\xff"#
2365
2366happyCheck :: HappyAddr
2367happyCheck = HappyA# "\xff\xff\x00\x00\x0d\x00\x53\x00\x05\x00\x06\x00\x23\x00\x24\x00\x06\x00\x39\x00\x0f\x00\x10\x00\x0f\x00\x10\x00\x13\x00\x11\x00\x13\x00\x13\x00\x53\x00\x10\x00\x0c\x00\x0d\x00\x13\x00\x12\x00\x13\x00\x14\x00\x13\x00\x14\x00\x53\x00\x18\x00\x08\x00\x09\x00\x0a\x00\x61\x00\x1b\x00\x04\x00\x1d\x00\x3a\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x04\x00\x09\x00\x0a\x00\x04\x00\x08\x00\x09\x00\x0a\x00\x08\x00\x09\x00\x0a\x00\x64\x00\x61\x00\x21\x00\x22\x00\x23\x00\x24\x00\x21\x00\x22\x00\x23\x00\x24\x00\x87\x00\x21\x00\x22\x00\x23\x00\x24\x00\x82\x00\xac\x00\x22\x00\x23\x00\x24\x00\x3b\x00\x3c\x00\x23\x00\x24\x00\x3b\x00\x3c\x00\x23\x00\x24\x00\x44\x00\xb0\x00\xb1\x00\x13\x00\x00\x00\x0a\x00\x13\x00\x00\x00\x13\x00\x00\x00\xaa\x00\x76\x00\x77\x00\x01\x00\x76\x00\x77\x00\x14\x00\x00\x00\xd6\x00\x48\x00\x48\x00\xd6\x00\x36\x00\xe8\x00\x87\x00\xaa\x00\x00\x00\x4e\x00\x4f\x00\x00\x00\x81\x00\x82\x00\x62\x00\x19\x00\x01\x00\xaa\x00\x11\x00\x35\x00\x70\x00\x52\x00\x35\x00\x36\x00\x25\x00\x13\x00\x4b\x00\x31\x00\x32\x00\x2a\x00\x2b\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x15\x00\x4b\x00\x29\x00\x2a\x00\x2b\x00\x61\x00\x4f\x00\xbd\x00\x13\x00\x49\x00\xc0\x00\xb5\x00\x11\x00\xc3\x00\xc4\x00\x87\x00\x76\x00\x77\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\x35\x00\xce\x00\xcf\x00\x61\x00\x61\x00\x63\x00\x54\x00\x87\x00\x1b\x01\x61\x00\x1d\x01\x45\x00\x52\x00\x52\x00\x4e\x00\x87\x00\x2e\x01\x5f\x00\x7e\x00\x35\x00\x27\x01\x75\x00\x62\x00\x69\x00\x69\x00\x54\x00\x87\x00\x64\x00\x57\x00\x7e\x00\x64\x00\x30\x01\x64\x00\x32\x01\x30\x01\x74\x00\xb5\x00\xbc\x00\x6f\x00\x78\x00\x64\x00\x62\x00\x87\x00\xf8\x00\xf9\x00\x87\x00\x33\x01\x87\x00\x70\x00\x64\x00\x73\x00\x6f\x00\x39\x01\x02\x01\x03\x01\x33\x01\x1e\x01\x06\x01\x07\x01\x21\x01\x6f\x00\x39\x01\xaf\x00\xb0\x00\xb1\x00\x27\x01\x1e\x01\xd3\x00\x21\x01\x21\x01\x33\x01\xd3\x00\x65\x00\x65\x00\x27\x01\x27\x01\x39\x01\x88\x00\x0f\x01\x10\x01\x11\x01\x1e\x01\x1f\x01\x20\x01\x21\x01\x33\x01\x08\x01\x60\x00\x21\x01\xa0\x00\x27\x01\x39\x01\x29\x01\x2a\x01\x27\x01\x33\x01\x2d\x01\x7e\x00\x14\x01\x15\x01\x82\x00\x39\x01\x02\x01\x03\x01\x0c\x00\x21\x01\x06\x01\x07\x01\x21\x01\x09\x01\x1e\x01\x27\x01\x56\x00\x21\x01\x27\x01\x25\x01\x26\x01\x62\x00\x28\x01\x27\x01\x1c\x00\x33\x01\x2c\x01\x35\x01\x36\x01\x19\x01\x0f\x01\x10\x01\x11\x01\x4e\x00\x6f\x00\x1f\x01\x20\x01\x21\x01\x22\x01\x2f\x01\x24\x01\x25\x01\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2f\x01\xab\x00\xac\x00\x2f\x01\x37\x01\x87\x00\x37\x01\x37\x01\x7f\x00\x2f\x01\x1d\x01\x1d\x01\x37\x01\x7b\x00\x37\x01\x27\x01\x37\x01\x0c\x00\x70\x00\x21\x01\x27\x01\x27\x01\x99\x00\x62\x00\x27\x01\x27\x01\x33\x01\x27\x01\x35\x01\x36\x01\x33\x01\x27\x01\x35\x01\x36\x01\x27\x01\x33\x01\x6f\x00\x35\x01\x36\x01\x79\x00\x33\x01\x34\x00\x35\x01\x36\x01\x33\x01\x41\x00\x35\x01\x36\x01\x33\x01\x33\x01\x35\x01\x36\x01\x0d\x01\x1d\x01\x0f\x01\x39\x01\x11\x01\x0d\x01\x00\x00\x0f\x01\x00\x00\x11\x01\x0d\x01\x27\x01\x0f\x01\x1e\x01\x11\x01\x1b\x01\x21\x01\x1d\x01\x1f\x01\x20\x01\x21\x01\x99\x00\x27\x01\x1f\x01\x20\x01\x21\x01\x27\x01\x27\x01\x1f\x01\x20\x01\x21\x01\x27\x01\x1e\x01\x39\x00\x4d\x00\x21\x01\x27\x01\x3d\x00\x3e\x00\x3f\x00\x40\x00\x27\x01\x42\x00\x4e\x00\x52\x00\x00\x00\x4d\x00\x56\x00\x4b\x00\x9f\x00\xa0\x00\x78\x00\x79\x00\x73\x00\x04\x01\x05\x01\x06\x01\x07\x01\x52\x00\x1e\x01\x4b\x00\x4b\x00\x21\x01\x6a\x00\x7e\x00\x89\x00\x5a\x00\x5b\x00\x27\x01\x70\x00\x00\x00\x5f\x00\x4e\x00\x91\x00\x70\x00\x76\x00\x64\x00\x70\x00\x96\x00\x97\x00\x98\x00\x99\x00\x71\x00\x21\x01\x6f\x00\x33\x01\x62\x00\x76\x00\x7f\x00\x27\x01\x57\x00\x39\x01\x2a\x01\xff\x00\x00\x01\x08\x01\x6f\x00\x6f\x00\x04\x01\x6f\x00\x06\x01\x07\x01\x7e\x00\x19\x00\x1e\x01\x39\x00\x64\x00\x21\x01\x64\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x27\x01\x42\x00\x4e\x00\xa9\x00\x6f\x00\x4e\x00\x6f\x00\xc0\x00\xff\x00\x00\x01\x2d\x00\x1e\x01\x66\x00\x04\x01\x21\x01\x06\x01\x07\x01\x52\x00\x2c\x01\x4f\x00\x27\x01\xce\x00\x52\x00\x2a\x01\x54\x00\x5a\x00\x5b\x00\x57\x00\x4b\x00\x00\x00\x5f\x00\xa0\x00\x64\x00\x9f\x00\xa0\x00\x64\x00\x70\x00\x7f\x00\x1f\x00\x1e\x01\x83\x00\x52\x00\x21\x01\x6f\x00\x00\x00\xb6\x00\xb7\x00\xb8\x00\x27\x01\x52\x00\x6a\x00\x2a\x01\xbd\x00\x2e\x00\x2f\x00\xc0\x00\x70\x00\x64\x00\xc3\x00\xc4\x00\x1b\x01\x7e\x00\x1d\x01\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\x6f\x00\xce\x00\xcf\x00\x70\x00\x27\x01\xff\x00\x00\x01\x6c\x00\x88\x00\x66\x00\x04\x01\x70\x00\x06\x01\x07\x01\x0b\x01\x0c\x01\x4b\x00\x0e\x01\x0f\x01\x70\x00\x11\x01\x12\x01\x13\x01\x70\x00\x9f\x00\xa0\x00\x04\x01\x05\x01\x06\x01\x07\x01\x1b\x01\x1c\x01\x1d\x01\x9f\x00\xa0\x00\x19\x00\x1e\x01\x9f\x00\xa0\x00\x21\x01\x19\x00\x4c\x00\x27\x01\xf8\x00\xf9\x00\x27\x01\x87\x00\x52\x00\x2a\x01\xb6\x00\xb7\x00\xb8\x00\x66\x00\x02\x01\x03\x01\x2d\x00\xbd\x00\x06\x01\x07\x01\xc0\x00\x19\x00\x64\x00\xc3\x00\xc4\x00\x2a\x01\x12\x01\x13\x01\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\x6f\x00\xce\x00\xcf\x00\x39\x00\x64\x00\x70\x00\x3f\x00\x40\x00\x2d\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x99\x00\x1b\x01\x6f\x00\x1d\x01\x1b\x01\x27\x01\x1d\x01\x29\x01\x2a\x01\x52\x00\x30\x01\x2d\x01\x19\x00\x27\x01\x51\x00\x52\x00\x27\x01\x33\x01\x34\x01\x35\x01\x36\x01\x09\x01\x6c\x00\x9f\x00\xa0\x00\x62\x00\x70\x00\x89\x00\x5f\x00\x53\x00\xf8\x00\xf9\x00\x2d\x00\x64\x00\x16\x01\x69\x00\x18\x01\x19\x01\x69\x00\x6a\x00\x02\x01\x03\x01\x98\x00\x99\x00\x06\x01\x07\x01\x22\x01\x53\x00\x24\x01\x25\x01\x26\x01\x62\x00\x28\x01\x4c\x00\x62\x00\x2b\x01\x2c\x01\x04\x01\x05\x01\x06\x01\x07\x01\x54\x00\x39\x00\x1b\x01\x6f\x00\x1d\x01\x1e\x00\x6f\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x1b\x01\x1a\x00\x1d\x01\x27\x01\x1b\x01\x27\x01\x1d\x01\x29\x01\x2a\x01\x2d\x00\xc0\x00\x2d\x01\x27\x01\x61\x00\x51\x00\x52\x00\x27\x01\x33\x01\x34\x01\x35\x01\x36\x01\x2e\x00\x2f\x00\x2a\x01\xce\x00\x2b\x01\x2c\x01\x66\x00\x5f\x00\x14\x00\x30\x01\x9f\x00\xa0\x00\x64\x00\x7f\x00\x62\x00\x1e\x00\x70\x00\x69\x00\x6a\x00\x58\x00\x59\x00\x5a\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x5f\x00\x6f\x00\x4d\x00\xbd\x00\x2d\x00\x52\x00\xc0\x00\xf4\x00\xf5\x00\xc3\x00\xc4\x00\x31\x00\x32\x00\x33\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x75\x00\x4f\x00\x7a\x00\x7b\x00\x79\x00\x53\x00\x1b\x01\x6a\x00\x1d\x01\x6a\x00\x74\x00\x1e\x00\x1e\x00\x70\x00\x78\x00\x70\x00\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\x76\x00\x11\x01\x12\x01\x13\x01\x7a\x00\x2d\x00\x2d\x00\x1f\x01\x20\x01\x21\x01\x30\x00\x1b\x01\x1c\x01\x1d\x01\x99\x00\x27\x01\xa7\x00\xa8\x00\xa9\x00\xf8\x00\xf9\x00\x3b\x00\x3c\x00\x27\x01\x62\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x02\x01\x03\x01\x66\x00\xbd\x00\x06\x01\x07\x01\xc0\x00\x6c\x00\x6f\x00\xc3\x00\xc4\x00\x70\x00\x70\x00\x62\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x39\x00\xf3\x00\xf4\x00\xf5\x00\x6f\x00\x55\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x04\x01\x05\x01\x06\x01\x07\x01\x1b\x01\x27\x01\x1d\x01\x29\x01\x2a\x01\x3f\x00\x40\x00\x2d\x01\x62\x00\xa7\x00\xa8\x00\xa9\x00\x27\x01\x33\x01\x34\x01\x35\x01\x36\x01\x04\x01\x05\x01\x06\x01\x07\x01\x6f\x00\x6a\x00\x1b\x01\x5f\x00\x1d\x01\xf8\x00\xf9\x00\x70\x00\x64\x00\x7e\x00\x1f\x01\x20\x01\x21\x01\x2a\x01\x27\x01\x02\x01\x03\x01\x6d\x00\x27\x01\x06\x01\x07\x01\x21\x01\x1d\x01\x04\x01\x05\x01\x06\x01\x07\x01\x27\x01\xff\x00\x00\x01\x2a\x01\x7e\x00\x27\x01\x04\x01\x2a\x01\x06\x01\x07\x01\x39\x00\x4e\x00\x4f\x00\x58\x00\x59\x00\x5a\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x5f\x00\x65\x00\x0f\x01\x6a\x00\x11\x01\x27\x01\x6c\x00\x29\x01\x2a\x01\x70\x00\x70\x00\x2d\x01\x1e\x01\x99\x00\x2a\x01\x21\x01\x1d\x01\x33\x01\x34\x01\x35\x01\x36\x01\x27\x01\x75\x00\x33\x01\x2a\x01\x99\x00\x27\x01\x57\x00\x5f\x00\x39\x01\x1f\x01\x20\x01\x21\x01\x64\x00\x04\x01\x05\x01\x06\x01\x07\x01\x27\x01\x61\x00\x69\x00\x63\x00\x6d\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x0a\x01\x0b\x01\x0c\x01\xbd\x00\x74\x00\x0f\x01\xc0\x00\x11\x01\x78\x00\xc3\x00\xc4\x00\x4d\x00\x4e\x00\x70\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x58\x00\x59\x00\x5a\x00\x2a\x01\x70\x00\x02\x01\x03\x01\x5f\x00\x89\x00\x06\x01\x07\x01\x65\x00\x33\x01\x6a\x00\x8f\x00\x69\x00\x91\x00\x6b\x00\x39\x01\x70\x00\x69\x00\x96\x00\x97\x00\x98\x00\x99\x00\x71\x00\x74\x00\x23\x00\x6c\x00\x75\x00\x76\x00\x74\x00\x70\x00\x79\x00\x7a\x00\x78\x00\x33\x01\x21\x01\xf6\x00\xf7\x00\xf8\x00\xf9\x00\x39\x01\x27\x01\x29\x01\x2a\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x02\x01\x03\x01\x21\x01\xbd\x00\x06\x01\x07\x01\xc0\x00\x74\x00\x27\x01\xc3\x00\xc4\x00\x78\x00\x08\x01\xc0\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x69\x00\x69\x00\x14\x01\x15\x01\x39\x00\xce\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x2c\x01\x61\x00\x74\x00\x63\x00\x30\x01\x27\x01\x78\x00\x29\x01\x2a\x01\x25\x01\x26\x01\x2d\x01\x28\x01\x3f\x00\x40\x00\x4e\x00\x2c\x01\x33\x01\x34\x01\x35\x01\x36\x01\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x20\x01\x21\x01\xf6\x00\xf7\x00\xf8\x00\xf9\x00\x5f\x00\x27\x01\x7e\x00\x29\x01\x2a\x01\x64\x00\x65\x00\x66\x00\x02\x01\x03\x01\x2d\x00\x2e\x00\x06\x01\x07\x01\x65\x00\x1f\x01\x20\x01\x21\x01\x69\x00\x87\x00\x6b\x00\x89\x00\x8a\x00\x27\x01\x0b\x01\x0c\x01\x99\x00\x0e\x01\x0f\x01\x74\x00\x11\x01\x12\x01\x13\x01\x78\x00\x39\x00\x99\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x1b\x01\x1c\x01\x1d\x01\x33\x01\x3a\x00\x27\x01\x34\x01\x29\x01\x2a\x01\x39\x01\x38\x01\x2d\x01\x27\x01\x25\x01\x26\x01\x4e\x00\x28\x01\x33\x01\x34\x01\x35\x01\x36\x01\x4d\x00\x4d\x00\x0c\x01\x54\x00\x35\x00\x0f\x01\x57\x00\x11\x01\x54\x00\x99\x00\x56\x00\x5f\x00\x58\x00\x59\x00\x5a\x00\x21\x01\x64\x00\x65\x00\x66\x00\x5f\x00\x13\x00\x27\x01\x1e\x01\x29\x01\x2a\x01\x21\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x34\x01\x27\x01\x4f\x00\xbd\x00\x38\x01\x52\x00\xc0\x00\x71\x00\x62\x00\xc3\x00\xc4\x00\x75\x00\x76\x00\x4d\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x4e\x00\x4f\x00\x58\x00\x59\x00\x5a\x00\xa2\x00\xa3\x00\xa4\x00\x89\x00\x5f\x00\x1e\x01\x65\x00\x1f\x00\x21\x01\x34\x01\x69\x00\x91\x00\x6b\x00\x38\x01\x27\x01\x6f\x00\x96\x00\x97\x00\x98\x00\x99\x00\x4f\x00\x74\x00\x71\x00\x52\x00\x4b\x00\x78\x00\x75\x00\x76\x00\x4e\x00\x4f\x00\x79\x00\x7a\x00\xa7\x00\xa8\x00\xa9\x00\xf8\x00\xf9\x00\x46\x00\x47\x00\x48\x00\x49\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x02\x01\x03\x01\x74\x00\xbd\x00\x06\x01\x07\x01\xc0\x00\x8f\x00\x65\x00\xc3\x00\xc4\x00\x02\x00\x03\x00\xc0\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x39\x00\x02\x00\x03\x00\x20\x01\x21\x01\xce\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x27\x01\x0c\x01\x29\x01\x2a\x01\x0f\x01\x27\x01\x11\x01\x29\x01\x2a\x01\x70\x00\x61\x00\x2d\x01\x63\x00\x4e\x00\x51\x00\x52\x00\x4f\x00\x33\x01\x34\x01\x35\x01\x36\x01\x1f\x01\x20\x01\x21\x01\x1f\x01\x20\x01\x21\x01\x54\x00\x5f\x00\x27\x01\xf8\x00\xf9\x00\x27\x01\x64\x00\x4b\x00\x24\x01\x25\x01\x26\x01\x69\x00\x28\x01\x02\x01\x03\x01\x2b\x01\x2c\x01\x06\x01\x07\x01\x4b\x00\x30\x01\x04\x01\x05\x01\x06\x01\x07\x01\x11\x00\x1f\x01\x20\x01\x21\x01\x0b\x01\x0c\x01\x4b\x00\x0e\x01\x0f\x01\x27\x01\x11\x01\x12\x01\x13\x01\xba\x00\xbb\x00\xbc\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x1b\x01\x1c\x01\x1d\x01\x4b\x00\x61\x00\x27\x01\x63\x00\x29\x01\x2a\x01\x52\x00\x0c\x01\x2d\x01\x27\x01\x0f\x01\x2a\x01\x11\x01\x57\x00\x33\x01\x34\x01\x35\x01\x36\x01\x99\x00\x45\x00\x33\x01\xba\x00\xbb\x00\xbc\x00\x4c\x00\x4d\x00\x39\x01\x0a\x01\x0b\x01\x0c\x01\x54\x00\x61\x00\x0f\x01\x63\x00\x11\x01\x24\x01\x25\x01\x26\x01\x7e\x00\x28\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x1b\x01\x39\x00\x1d\x01\xbd\x00\x6a\x00\x61\x00\xc0\x00\x63\x00\x70\x00\xc3\x00\xc4\x00\x4e\x00\x27\x01\xc0\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x4e\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xce\x00\x00\x01\xe4\x00\xe5\x00\xe6\x00\x04\x01\xe8\x00\x06\x01\x07\x01\x24\x01\x25\x01\x26\x01\x5f\x00\x28\x01\x89\x00\x6e\x00\x6f\x00\x64\x00\x65\x00\x01\x01\x6a\x00\x03\x01\x91\x00\x61\x00\x06\x01\x63\x00\x6a\x00\x96\x00\x97\x00\x98\x00\x99\x00\x1e\x01\x6e\x00\x6f\x00\x21\x01\xf8\x00\xf9\x00\xbe\x00\xbf\x00\x99\x00\x27\x01\x6a\x00\x61\x00\x2a\x01\x63\x00\x02\x01\x03\x01\x6a\x00\x1e\x01\x06\x01\x07\x01\x21\x01\x5c\x00\x5d\x00\x5e\x00\x4b\x00\x52\x00\x27\x01\x54\x00\x29\x01\x2a\x01\x0b\x01\x0c\x01\x52\x00\x61\x00\x0f\x01\x63\x00\x11\x01\x0d\x00\xc0\x00\xb2\x00\xb3\x00\xb4\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x1b\x01\xc0\x00\x1d\x01\xbe\x00\xbf\x00\x27\x01\xce\x00\x29\x01\x2a\x01\xbe\x00\xbf\x00\x2d\x01\x27\x01\x70\x00\x61\x00\xce\x00\x63\x00\x33\x01\x34\x01\x35\x01\x36\x01\x66\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x39\x00\x25\x01\x26\x01\xbd\x00\x28\x01\x61\x00\xc0\x00\x63\x00\x2c\x01\xc3\x00\xc4\x00\x61\x00\x30\x01\x63\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xb2\x00\xb3\x00\xb4\x00\xb2\x00\xb3\x00\xb4\x00\xb2\x00\xb3\x00\xb4\x00\xb2\x00\xb3\x00\xb4\x00\xb2\x00\xb3\x00\xb4\x00\x61\x00\x5f\x00\x63\x00\x91\x00\x0b\x01\x0c\x01\x64\x00\x0e\x01\x0f\x01\x8f\x00\x11\x01\x12\x01\x13\x01\x0b\x01\x0c\x01\x6d\x00\x61\x00\x0f\x01\x63\x00\x11\x01\x1b\x01\x1c\x01\x1d\x01\x45\x00\x46\x00\xf8\x00\xf9\x00\x6a\x00\x61\x00\x1b\x01\x63\x00\x1d\x01\x27\x01\x71\x00\x72\x00\x02\x01\x03\x01\x73\x00\x74\x00\x06\x01\x07\x01\x27\x01\x65\x00\x31\x01\x32\x01\xe6\x00\x69\x00\xe8\x00\x6b\x00\x12\x01\x13\x01\x8f\x00\x6f\x00\x6e\x00\x6f\x00\xf7\x00\xf8\x00\x74\x00\x6c\x00\x4d\x00\xa3\x00\xa4\x00\x6a\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x8f\x00\x56\x00\x66\x00\x58\x00\x59\x00\x27\x01\x70\x00\x29\x01\x2a\x01\x87\x00\x5f\x00\x2d\x01\x36\x00\x37\x00\x54\x00\x4c\x00\x4d\x00\x33\x01\x34\x01\x35\x01\x36\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x39\x00\x7f\x00\x4b\x00\xbd\x00\x4b\x00\x4b\x00\xc0\x00\x75\x00\x76\x00\xc3\x00\xc4\x00\x79\x00\x7a\x00\x0d\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x6f\x00\x52\x00\x15\x00\x71\x00\x71\x00\x6a\x00\x6a\x00\x6a\x00\x6a\x00\x6a\x00\x71\x00\x71\x00\x6c\x00\x62\x00\x6c\x00\x6a\x00\x5f\x00\x0c\x00\x6a\x00\x34\x00\x19\x00\x64\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\x58\x00\x00\x01\x6f\x00\x89\x00\x6d\x00\x04\x01\x4e\x00\x06\x01\x07\x01\x70\x00\x70\x00\x91\x00\x71\x00\x6a\x00\xf8\x00\xf9\x00\x96\x00\x97\x00\x98\x00\x99\x00\x6a\x00\x6a\x00\x6a\x00\x6a\x00\x02\x01\x03\x01\x00\x01\x6a\x00\x06\x01\x07\x01\x04\x01\x1e\x01\x06\x01\x07\x01\x21\x01\x6a\x00\x6a\x00\x6a\x00\x25\x01\x26\x01\x27\x01\x28\x01\x66\x00\x2a\x01\x70\x00\x2c\x01\x62\x00\x4d\x00\x70\x00\x30\x01\x4f\x00\x54\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x1e\x01\x70\x00\xc0\x00\x21\x01\x17\x00\x27\x01\x4d\x00\x29\x01\x2a\x01\x27\x01\x54\x00\x2d\x01\x2a\x01\x70\x00\x52\x00\x62\x00\xce\x00\x33\x01\x34\x01\x35\x01\x36\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x39\x00\x6a\x00\x57\x00\xbd\x00\x4e\x00\x70\x00\xc0\x00\x4f\x00\x4b\x00\xc3\x00\xc4\x00\x4b\x00\x4e\x00\x66\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x4e\x00\x7f\x00\x4b\x00\x6a\x00\x89\x00\x6a\x00\x4b\x00\x71\x00\x71\x00\x19\x00\x52\x00\x57\x00\x91\x00\x4e\x00\x70\x00\x4e\x00\x5f\x00\x96\x00\x97\x00\x98\x00\x99\x00\x64\x00\x6a\x00\x19\x00\x01\x01\x4f\x00\x03\x01\x1a\x00\x4b\x00\x06\x01\x0b\x01\x0c\x01\x09\x01\x0e\x01\x0f\x01\x74\x00\x11\x01\x12\x01\x13\x01\x7e\x00\xf8\x00\xf9\x00\x4b\x00\x7e\x00\x15\x01\x16\x00\x1b\x01\x1c\x01\x1d\x01\x0c\x00\x02\x01\x03\x01\x6f\x00\x1e\x01\x06\x01\x07\x01\x21\x01\x4d\x00\x27\x01\xc0\x00\x25\x01\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x58\x00\x59\x00\x5a\x00\x4d\x00\x4b\x00\xce\x00\x69\x00\x5f\x00\x7e\x00\x66\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\x19\x00\x62\x00\x70\x00\x4e\x00\x6a\x00\x27\x01\x4e\x00\x29\x01\x2a\x01\x71\x00\x70\x00\x2d\x01\x4e\x00\x4e\x00\x4e\x00\x75\x00\x76\x00\x33\x01\x34\x01\x35\x01\x36\x01\xb6\x00\xb7\x00\xb8\x00\xb9\x00\x5f\x00\x52\x00\x4f\x00\xbd\x00\x70\x00\x19\x00\xc0\x00\x19\x00\x54\x00\xc3\x00\xc4\x00\x07\x00\x4f\x00\x57\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\x4d\x00\x4b\x00\x89\x00\x52\x00\x54\x00\x0b\x01\x0c\x01\x66\x00\x0e\x01\x0f\x01\x91\x00\x11\x01\x12\x01\x13\x01\x7b\x00\x96\x00\x97\x00\x98\x00\x99\x00\x7f\x00\x6f\x00\x1b\x01\x1c\x01\x1d\x01\x6f\x00\xfd\x00\xfe\x00\x62\x00\x00\x01\x52\x00\x6a\x00\x88\x00\x04\x01\x27\x01\x06\x01\x07\x01\x4d\x00\x66\x00\x69\x00\x19\x00\xf8\x00\xf9\x00\x19\x00\x6a\x00\x6a\x00\x6f\x00\x88\x00\x87\x00\x19\x00\x58\x00\x02\x01\x03\x01\x52\x00\x2d\x00\x06\x01\x07\x01\x6f\x00\xc0\x00\x1e\x01\x4f\x00\x89\x00\x21\x01\x70\x00\x4b\x00\x4b\x00\x19\x00\x5f\x00\x27\x01\x91\x00\x07\x00\x2a\x01\xce\x00\x07\x00\x96\x00\x97\x00\x98\x00\x99\x00\x87\x00\x1e\x01\x1f\x01\x20\x01\x21\x01\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\x27\x01\x00\x01\x29\x01\x2a\x01\x19\x00\x04\x01\x2d\x01\x06\x01\x07\x01\x89\x00\x4e\x00\x5f\x00\x33\x01\x34\x01\x35\x01\x36\x01\x66\x00\x91\x00\x57\x00\x19\x00\x7e\x00\x4b\x00\x96\x00\x97\x00\x98\x00\x99\x00\x4b\x00\x19\x00\xc0\x00\x6f\x00\x16\x00\x1e\x01\x4e\x00\x1a\x00\x21\x01\x4f\x00\x54\x00\x11\x00\x23\x00\x33\x00\x27\x01\x88\x00\xce\x00\x2a\x01\x1a\x00\x0b\x01\x0c\x01\x07\x00\x0e\x01\x0f\x01\x7f\x00\x11\x01\x12\x01\x13\x01\x4d\x00\x4e\x00\x4f\x00\x09\x00\x65\x00\x52\x00\x69\x00\x1b\x01\x1c\x01\x1d\x01\xc0\x00\x58\x00\x59\x00\x5a\x00\x89\x00\x6a\x00\x3a\x00\x69\x00\x5f\x00\x27\x01\x8f\x00\x4d\x00\x91\x00\x2e\x00\xce\x00\x57\x00\x70\x00\x96\x00\x97\x00\x98\x00\x99\x00\x6f\x00\x52\x00\x02\x01\x03\x01\x6a\x00\x71\x00\x06\x01\x07\x01\x4e\x00\x75\x00\x76\x00\x6f\x00\x62\x00\x79\x00\x7a\x00\x02\x00\x45\x00\x6a\x00\x0b\x01\x0c\x01\x4e\x00\x0e\x01\x0f\x01\x62\x00\x11\x01\x12\x01\x13\x01\x5f\x00\x58\x00\x62\x00\x57\x00\x1f\x01\x20\x01\x21\x01\x1b\x01\x1c\x01\x1d\x01\x88\x00\xc0\x00\x27\x01\x5f\x00\x29\x01\x2a\x01\x7f\x00\x6a\x00\x6a\x00\x27\x01\x58\x00\x70\x00\x70\x00\x6a\x00\x4b\x00\xce\x00\x02\x00\x0b\x01\x0c\x01\x6a\x00\x0e\x01\x0f\x01\x6a\x00\x11\x01\x12\x01\x13\x01\x69\x00\x87\x00\x52\x00\x52\x00\x69\x00\x19\x00\x07\x00\x1b\x01\x1c\x01\x1d\x01\x6a\x00\x4e\x00\x19\x00\x69\x00\x89\x00\x75\x00\x4d\x00\x19\x00\x07\x00\x27\x01\x8f\x00\x6a\x00\x91\x00\x75\x00\x30\x00\x30\x01\xed\x00\x96\x00\x97\x00\x98\x00\x99\x00\xed\x00\xed\x00\x89\x00\xd2\x00\x38\x00\x59\x00\x43\x00\x7f\x00\x8f\x00\x31\x00\x91\x00\x2e\x01\x32\x00\x2f\x01\x2f\x01\x96\x00\x97\x00\x98\x00\x99\x00\x0b\x01\x0c\x01\x7c\x00\x0e\x01\x0f\x01\x7c\x00\x11\x01\x12\x01\x13\x01\x11\x01\x80\x00\x59\x00\x80\x00\xa1\x00\x30\x01\xd0\x00\x1b\x01\x1c\x01\x1d\x01\xc0\x00\x84\x00\xe0\x00\xff\x00\x00\x01\x8a\x00\x2f\x01\xc6\x00\x04\x01\x27\x01\x06\x01\x07\x01\x85\x00\x86\x00\xce\x00\x2f\x01\x89\x00\x16\x00\x2e\x01\xc0\x00\x8d\x00\x8e\x00\x8f\x00\x16\x00\x91\x00\x92\x00\x30\x00\x03\x00\xe8\x00\x96\x00\x97\x00\x98\x00\x99\x00\xce\x00\x1e\x01\x2e\x01\x34\x01\x21\x01\x34\x01\x68\x00\xe0\x00\x54\x00\x43\x00\x27\x01\x2e\x01\x2e\x01\x2a\x01\x2e\x01\x6c\x00\x55\x00\x2a\x01\x86\x00\x72\x00\x75\x00\x89\x00\x34\x00\x7d\x00\x16\x00\x16\x00\x8e\x00\x8f\x00\x2c\x00\x20\x00\x92\x00\x20\x00\x7c\x00\x33\x00\x96\x00\x97\x00\x98\x00\x99\x00\xc0\x00\x7c\x00\x63\x00\x5e\x00\x0b\x01\x0c\x01\x47\x00\x0e\x01\x0f\x01\x6b\x00\x11\x01\x12\x01\x13\x01\x67\x00\xce\x00\xa6\x00\x8a\x00\x70\x00\x8a\x00\x2c\x00\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\x2e\x01\x0e\x01\x0f\x01\x0e\x00\x11\x01\x12\x01\x13\x01\x27\x01\x20\x00\x20\x00\xc6\x00\xe8\x00\x70\x00\xc0\x00\x1b\x01\x1c\x01\x1d\x01\xa6\x00\xb4\x00\x4a\x00\xa4\x00\x86\x00\x17\x00\x17\x00\x89\x00\x34\x00\x27\x01\xce\x00\x4b\x00\x8e\x00\x8f\x00\xf8\x00\x2f\x01\x92\x00\x50\x00\x02\x00\x50\x00\x96\x00\x97\x00\x98\x00\x99\x00\x4f\x00\x2e\x01\x0a\x00\x2e\x01\xad\x00\x34\x01\x45\x00\x1c\x00\x2e\x01\x0b\x01\x0c\x01\x26\x00\x0e\x01\x0f\x01\x16\x00\x11\x01\x12\x01\x13\x01\x1c\x00\x2f\x01\x1c\x00\x1d\x00\x1e\x00\x0b\x00\x31\x00\x1b\x01\x1c\x01\x1d\x01\xf8\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2f\x01\x56\x00\x2c\x00\x27\x01\xc0\x00\x2e\x01\x59\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0b\x01\x0c\x01\x33\x01\x0e\x01\x0f\x01\xce\x00\x11\x01\x12\x01\x13\x01\x2e\x01\x35\x00\x2e\x01\x2e\x01\x4d\x00\x2f\x01\x2e\x01\x1b\x01\x1c\x01\x1d\x01\x54\x00\x54\x00\x16\x00\x56\x00\x56\x00\x58\x00\x59\x00\x5a\x00\x86\x00\x27\x01\x16\x00\x89\x00\x5f\x00\x2f\x01\x20\x00\x2f\x01\x8e\x00\x8f\x00\xa6\x00\x20\x00\x92\x00\x33\x01\x17\x00\x6a\x00\x96\x00\x97\x00\x98\x00\x99\x00\xf8\x00\x70\x00\x17\x00\xff\xff\x2f\x01\x2f\x01\x75\x00\x76\x00\xff\xff\x2f\x01\x79\x00\x7a\x00\xff\xff\x73\x00\x74\x00\x75\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\x7e\x00\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xc0\x00\x54\x00\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\x86\x00\x27\x01\xff\xff\x89\x00\x5f\x00\xff\xff\xce\x00\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\x33\x01\xff\xff\x6a\x00\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\x75\x00\x76\x00\xff\xff\xff\xff\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x86\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8e\x00\x8f\x00\xf8\x00\xff\xff\x92\x00\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xce\x00\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xc0\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\x33\x01\x86\x00\xff\xff\xce\x00\x89\x00\xff\xff\xff\xff\xf8\x00\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xeb\x00\xec\x00\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xf8\x00\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x27\x01\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x33\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xce\x00\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\x86\x00\x27\x01\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\x33\x01\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x89\x00\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\x1b\x01\x1c\x01\x1d\x01\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x90\x00\x27\x01\xce\x00\x93\x00\x94\x00\x95\x00\x4d\x00\xc0\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x33\x01\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xce\x00\xff\xff\x89\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xae\x00\xff\xff\xff\xff\xff\xff\x94\x00\x95\x00\xff\xff\xff\xff\x98\x00\x99\x00\xff\xff\xff\xff\x89\x00\xff\xff\xf8\x00\xff\xff\x75\x00\x76\x00\xc0\x00\xff\xff\x79\x00\x7a\x00\xff\xff\xff\xff\x95\x00\xff\xff\xff\xff\x98\x00\x99\x00\xff\xff\xae\x00\xff\xff\xce\x00\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x27\x01\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\x1b\x01\x1c\x01\x1d\x01\xff\xff\x4d\x00\x33\x01\x4f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xce\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x1b\x01\x1c\x01\x1d\x01\x75\x00\x76\x00\xff\xff\xff\xff\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\x34\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x27\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\x89\x00\x34\x01\xff\xff\xff\xff\x8d\x00\x8e\x00\x8f\x00\x27\x01\x91\x00\x92\x00\xff\xff\xff\xff\x4d\x00\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x34\x01\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x89\x00\x5f\x00\xff\xff\xff\xff\x8d\x00\x8e\x00\x8f\x00\xff\xff\x91\x00\x92\x00\xff\xff\xff\xff\x6a\x00\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\x75\x00\x76\x00\xff\xff\xc0\x00\x79\x00\x7a\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\x8e\x00\x8f\x00\xff\xff\x91\x00\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\x8c\x00\x09\x01\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x16\x01\x9b\x00\x18\x01\x19\x01\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x22\x01\xff\xff\x24\x01\x25\x01\x26\x01\xff\xff\x28\x01\xff\xff\xff\xff\x2b\x01\x2c\x01\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\x89\x00\xff\xff\xff\xff\x8c\x00\xff\xff\x8e\x00\x8f\x00\xff\xff\x27\x01\x92\x00\xff\xff\xff\xff\x4d\x00\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\x9b\x00\xff\xff\x33\x01\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x89\x00\x5f\x00\xff\xff\x8c\x00\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x71\x00\xff\xff\xff\xff\xff\xff\x75\x00\x76\x00\xff\xff\xc0\x00\x79\x00\x7a\x00\x89\x00\xff\xff\xff\xff\x8c\x00\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x09\x01\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x16\x01\xff\xff\x18\x01\x19\x01\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x22\x01\xff\xff\x24\x01\x25\x01\x26\x01\xff\xff\x28\x01\xff\xff\xff\xff\x2b\x01\x2c\x01\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8e\x00\x8f\x00\xff\xff\x27\x01\x92\x00\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x09\x01\x8e\x00\x8f\x00\xff\xff\xff\xff\x92\x00\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x16\x01\xff\xff\x18\x01\x19\x01\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x22\x01\xff\xff\x24\x01\x25\x01\x26\x01\xff\xff\x28\x01\xff\xff\xff\xff\x2b\x01\x2c\x01\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\x33\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xc0\x00\xff\xff\xff\xff\x9d\x00\x9e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x4d\x00\x4e\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\xc0\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\x71\x00\xff\xff\xff\xff\xff\xff\x75\x00\x76\x00\xff\xff\xff\xff\x79\x00\x7a\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x25\x01\x26\x01\x27\x01\x28\x01\xff\xff\xff\xff\x2b\x01\x2c\x01\x09\x01\xff\xff\xff\xff\x30\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x16\x01\xff\xff\x18\x01\x19\x01\xf8\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\x22\x01\xff\xff\x24\x01\x25\x01\x26\x01\xff\xff\x28\x01\x27\x01\xff\xff\x2b\x01\x2c\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\x30\x01\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\x30\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\x02\x00\xce\x00\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\x0a\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xff\xff\xff\xff\xff\xff\xc0\x00\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xf8\x00\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xce\x00\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\x30\x01\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\x1b\x01\x1c\x01\x1d\x01\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\xff\xff\xff\xff\x88\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\xc0\x00\xff\xff\x88\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\xc0\x00\xff\xff\x88\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x85\x00\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x9c\x00\x9d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x9c\x00\x9d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x9d\x00\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x9d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\x9e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x9d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\x9d\x00\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xa0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xc0\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xa5\x00\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xeb\x00\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xf8\x00\xf9\x00\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xc0\x00\xff\xff\xa5\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\x27\x01\xa5\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xc0\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xa5\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xa5\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xf8\x00\xf9\x00\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xc0\x00\xff\xff\xa5\x00\x89\x00\xff\xff\x8b\x00\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xc0\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xa5\x00\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xf8\x00\xf9\x00\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xc0\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xce\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xf8\x00\xff\xff\xc0\x00\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\x27\x01\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\x8d\x00\xff\xff\x8f\x00\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x91\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x89\x00\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x91\x00\x4d\x00\x4e\x00\xf8\x00\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xce\x00\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\xff\xff\xc0\x00\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xf8\x00\xff\xff\xff\xff\xce\x00\xff\xff\x71\x00\x1b\x01\x1c\x01\x1d\x01\x75\x00\x76\x00\xff\xff\xff\xff\x79\x00\x7a\x00\xc0\x00\xff\xff\xff\xff\x27\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x27\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\x91\x00\x11\x01\x12\x01\x13\x01\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\x91\x00\x11\x01\x12\x01\x13\x01\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xc0\x00\xff\xff\x27\x01\xff\xff\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xce\x00\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x91\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x91\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x27\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\x91\x00\x11\x01\x12\x01\x13\x01\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\xff\xff\x91\x00\xff\xff\xff\xff\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\x89\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x91\x00\xff\xff\xc0\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\x4d\x00\x4e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x89\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x91\x00\x5f\x00\xc0\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xce\x00\xff\xff\x89\x00\x71\x00\xff\xff\xc0\x00\xff\xff\x75\x00\x76\x00\xff\xff\xff\xff\x79\x00\x7a\x00\xff\xff\xff\xff\x96\x00\x97\x00\x98\x00\x99\x00\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xce\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\x0b\x01\x0c\x01\xff\xff\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\x27\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x01\x1c\x01\x1d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x01\x0c\x01\x27\x01\x0e\x01\x0f\x01\xff\xff\x11\x01\x12\x01\x13\x01\xff\xff\xff\xff\x00\x00\x01\x00\x02\x00\x03\x00\xff\xff\x1b\x01\x1c\x01\x1d\x01\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x64\x00\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\x6f\x00\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\xff\xff\x14\x00\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\x43\x00\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\x06\x00\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\x14\x00\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\x06\x00\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\x14\x00\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\x6c\x00\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\x6c\x00\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x66\x00\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\x4e\x00\x4f\x00\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\x4e\x00\x4f\x00\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\x0e\x00\x0f\x00\x10\x00\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x44\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\x6f\x00\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\x17\x00\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\x6f\x00\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\x17\x00\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\xff\xff\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\x51\x00\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x60\x00\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x60\x00\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\xff\xff\xff\xff\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\xff\xff\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\xff\xff\x08\x00\xff\xff\x0a\x00\x0b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x12\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\x01\x00\x02\x00\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\x0a\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\x6e\x00\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\x01\x00\x02\x00\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\x0a\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\x6d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\xff\xff\x01\x00\x02\x00\xff\xff\x8b\x00\x8c\x00\x8d\x00\x8e\x00\xff\xff\x90\x00\x0a\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x54\x00\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\x6c\x00\xff\xff\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xc4\x00\x87\x00\xff\xff\x0a\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\x66\x00\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xeb\x00\xec\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\x87\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x88\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xcc\x00\xff\xff\xce\x00\xcf\x00\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\x1f\x01\x20\x01\x21\x01\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x27\x01\x6b\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x88\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x88\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x88\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x56\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x60\x00\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\x79\x00\x7a\x00\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\xff\xff\x16\x00\xff\xff\x97\x00\x98\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x02\x00\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\x0a\x00\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x61\x00\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x72\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\x78\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7e\x00\x7f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x00\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\x92\x00\x93\x00\x73\x00\xff\xff\xff\xff\x97\x00\x98\x00\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\x7e\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7e\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7e\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\x7e\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x54\x00\xff\xff\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\x02\x00\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\x71\x00\xff\xff\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x01\x00\x02\x00\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\x71\x00\xff\xff\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\x78\x00\xff\xff\x7a\x00\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x13\x00\xff\xff\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\x13\x00\xff\xff\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x2f\x00\x69\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x70\x00\xff\xff\xff\xff\x73\x00\x74\x00\x02\x00\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x69\x00\x02\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x02\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\x4c\x00\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x69\x00\x02\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x65\x00\x02\x00\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\x78\x00\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\x77\x00\x78\x00\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\x02\x00\xff\xff\xff\xff\x69\x00\xff\xff\x6b\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\x78\x00\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\x78\x00\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\x78\x00\x4c\x00\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\x69\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\xff\xff\x77\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\xc0\x00\xc1\x00\xc2\x00\x77\x00\xc4\x00\xc5\x00\x4d\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\x58\x00\x59\x00\x5a\x00\xd4\x00\xd5\x00\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x6a\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\x73\x00\x74\x00\x75\x00\x76\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\x25\x01\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xff\xff\xff\xff\x30\x01\x02\x00\x32\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\x0a\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\x16\x00\xff\xff\xd4\x00\xd5\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x54\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\x25\x01\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xff\xff\x73\x00\x30\x01\xff\xff\x32\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xd5\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\x02\x00\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\x0a\x00\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\x13\x00\xff\xff\x30\x01\x16\x00\x32\x01\x18\x00\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x02\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x65\x00\xff\xff\x2c\x00\xff\xff\x69\x00\x02\x00\x6b\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x02\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x65\x00\xff\xff\x2c\x00\xff\xff\x69\x00\x02\x00\x6b\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x69\x00\x02\x00\x6b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x65\x00\xff\xff\x2c\x00\xff\xff\x69\x00\x02\x00\x6b\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\x73\x00\x74\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\x02\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\x73\x00\x74\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\x74\x00\xff\xff\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4f\x00\x0a\x00\xff\xff\xff\xff\x53\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\x61\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x70\x00\xff\xff\x2c\x00\x73\x00\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\x1a\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\x02\x00\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\x73\x00\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xe1\x00\xe2\x00\xe3\x00\xff\xff\xff\xff\x69\x00\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x73\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\x1f\x01\x20\x01\x21\x01\xd8\x00\xd9\x00\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\x2e\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xd7\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xd7\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xd4\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\x09\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x01\x18\x01\xff\xff\x1a\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\x23\x01\x24\x01\xff\xff\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xda\x00\xdb\x00\xdc\x00\xdd\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xdb\x00\xdc\x00\xdd\x00\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf0\x00\xf1\x00\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xef\x00\xff\xff\xf1\x00\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xee\x00\xff\xff\xff\xff\xf1\x00\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xee\x00\xff\xff\xff\xff\xf1\x00\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xde\x00\xdf\x00\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xe1\x00\xe2\x00\xe3\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xde\x00\xdf\x00\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xe1\x00\xe2\x00\xe3\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xe6\x00\xe7\x00\xe8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf1\x00\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xdd\x00\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xea\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf2\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xe3\x00\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xe9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xc1\x00\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xff\xff\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xff\xff\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xff\xff\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xc0\x00\xff\xff\xc2\x00\xff\xff\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xc0\x00\xff\xff\x06\x01\x07\x01\xc4\x00\xc5\x00\xff\xff\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xff\xff\xce\x00\xcf\x00\xff\xff\xff\xff\xff\xff\xc0\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xcc\x00\xff\xff\xce\x00\xcf\x00\x27\x01\xd1\x00\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xf8\x00\xf9\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x02\x01\x03\x01\xff\xff\xff\xff\x06\x01\x07\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x01\x20\x01\x21\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x01\xff\xff\x29\x01\x2a\x01\xff\xff\xff\xff\x2d\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
2368
2369happyTable :: HappyAddr
2370happyTable = HappyA# "\x00\x00\x70\x00\x84\x05\x62\x03\x43\x05\x44\x05\xa4\x04\x9c\x04\x86\x05\xce\x00\x97\x04\x94\x04\x93\x04\x94\x04\x95\x04\x0e\x01\x95\x04\x0f\x01\x03\x04\x27\x05\x40\x05\x41\x05\x95\x04\x10\x01\x11\x01\x12\x01\x2d\x00\x2e\x00\x6e\x05\x13\x01\x13\x02\x14\x02\x15\x02\xf7\x02\x2f\x00\x88\x05\x30\x00\x92\x02\x89\x05\xb5\x04\x14\x02\x15\x02\xb4\x04\x14\x02\xd1\x03\x23\x05\xb5\x04\x14\x02\x15\x02\xb5\x04\x14\x02\x15\x02\xcf\x00\x32\x03\x99\x04\x9a\x04\x9b\x04\x9c\x04\x6b\x05\x9a\x04\x9b\x04\x9c\x04\xa2\x02\x90\x05\x9a\x04\x9b\x04\x9c\x04\x3d\x03\x72\x05\x81\x05\x82\x05\x9c\x04\x88\x02\x89\x02\x33\x05\x9c\x04\x88\x02\x89\x02\x28\x05\x9c\x04\x6f\x04\x90\x04\xee\x01\xbf\xff\x11\x02\x68\x05\xbf\xff\x11\x02\xbf\xff\x11\x02\x63\x03\x2e\x04\x2f\x04\x4b\x03\x4a\x04\x2f\x04\x74\x04\x11\x02\x80\x02\x53\x04\x8d\x05\x95\x03\x97\x04\x64\x02\x34\x00\x04\x04\x11\x02\x66\x03\xbd\xfc\xff\xff\x36\x03\x37\x03\x3e\xfe\x5d\x03\x34\x00\x6f\x05\x58\x01\xbf\xff\x5a\x03\xbd\xfc\xbf\xff\x97\x04\xa5\x04\x06\x02\xb7\x02\x75\x04\x76\x04\xa6\x04\xa7\x04\x37\x05\x38\x05\x39\x05\x3a\x05\xa7\x04\x35\x00\x6b\x03\x83\x05\x3a\x05\xa7\x04\x37\x00\x79\x05\xd0\x00\xb8\x04\xfb\x04\x90\x00\xcb\x04\x7d\x01\xd1\x00\xd2\x00\x07\x01\xf7\x04\x2f\x04\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x07\x02\x9b\x00\x9c\x00\xb2\x01\x33\x00\xb3\x01\x24\x02\x07\x01\x20\x02\x15\x01\x4c\x00\x59\x01\xbb\x01\xd8\x02\xec\x02\x07\x01\x65\x02\x25\x02\xb8\x02\xb9\x04\x4d\x00\x7a\x05\x30\x03\x69\x05\x77\x04\x8c\x03\x34\x00\x12\x02\x92\xfe\x6c\x03\x12\x02\x81\x02\x12\x02\x82\x02\x81\x02\x64\x00\x70\x04\x5b\x03\x13\x02\x67\x00\x12\x02\x4e\x04\x34\x00\xa1\x00\xa2\x00\x34\x00\xef\x01\x34\x00\xed\x02\x12\x02\x4c\x03\xae\x03\x7a\x04\xa3\x00\x72\x00\xef\x01\x26\x02\x73\x00\x74\x00\x21\x01\x83\x03\xf0\x01\xec\x01\xed\x01\xee\x01\x11\x00\x38\x03\x8b\x02\xf8\x02\x21\x01\xef\x01\x8a\x02\x03\x03\x7b\x01\x11\x00\x11\x00\x64\x03\x08\x01\x71\x04\x72\x04\x47\x00\xd3\x00\xa4\x00\x0f\x00\xd4\x00\xef\x01\x93\x02\x30\x01\xf8\x02\x1f\x04\x11\x00\x64\x03\x7c\x00\x7d\x00\x11\x00\xef\x01\xa5\x00\x04\x03\x94\x02\x95\x02\x28\x04\x64\x03\x71\x00\x72\x00\x37\x01\x30\x04\x73\x00\x74\x00\x30\x04\x75\x00\x38\x03\x11\x00\xb4\x02\x21\x01\x11\x00\xda\x01\x7a\x00\x1b\x02\x7b\x00\x11\x00\x38\x01\x9d\x04\x96\x02\x9e\x04\x9f\x04\x76\x00\x71\x04\x72\x04\x47\x00\x56\xff\x13\x02\x0e\x00\x0f\x00\x10\x00\x77\x00\x42\x05\x78\x00\x79\x00\x7a\x00\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x45\x05\x78\x04\x79\x04\x45\x05\x31\x00\x25\x02\x31\x00\x31\x00\xb5\x02\x42\x05\x54\x04\x54\x04\x31\x00\x26\x03\x31\x00\x16\x02\x31\x00\x0e\x01\x56\xff\x30\x04\x4d\x00\x4d\x00\xff\xff\xad\x03\x16\x02\x11\x00\x9d\x04\x16\x02\x9e\x04\x9f\x04\x9d\x04\x16\x02\x9e\x04\x9f\x04\x16\x02\x9d\x04\xae\x03\x9e\x04\x9f\x04\x24\x03\x9d\x04\x01\x02\x9e\x04\x9f\x04\x9d\x04\x38\x01\x9e\x04\x9f\x04\x9d\x04\xef\x01\x9e\x04\x9f\x04\xa8\x04\xfc\x04\xa9\x04\xf0\x01\x47\x00\xa8\x04\x11\x02\xa9\x04\x11\x02\x47\x00\xa8\x04\x4d\x00\xa9\x04\x31\x03\x47\x00\xf7\x01\x21\x01\x4c\x00\xaa\x04\x0f\x00\x10\x00\xff\xff\x11\x00\xaa\x04\x0f\x00\x10\x00\x11\x00\x4d\x00\xaa\x04\x0f\x00\x10\x00\x11\x00\x31\x03\xce\x00\x81\x00\x21\x01\x11\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\x11\x00\xe9\x00\xc4\x03\x36\x02\x11\x02\x81\x00\x2b\x03\x09\x03\xf5\x01\xf6\x01\x26\x01\x27\x01\xad\x01\x31\x01\x32\x01\x73\x00\x1f\x01\xea\x00\x38\x03\x05\x03\x00\x03\x21\x01\x6c\x01\xae\x01\x37\x00\xeb\x00\xec\x00\x11\x00\x6d\x01\x11\x02\xed\x00\xfe\x01\x39\x01\x37\x02\x8d\x00\xcf\x00\x88\x03\x3a\x01\x3d\x00\x3e\x00\x3f\x00\xf6\x02\x33\x01\x0a\x03\xef\x01\x82\x03\x8d\x00\x2c\x03\x11\x00\xfd\x01\x7a\x04\x22\x01\x2c\x01\x29\x01\xf4\x02\x06\x03\x01\x03\x1e\x01\x83\x03\x73\x00\x1f\x01\xee\x00\x17\x01\x26\x02\xce\x00\x12\x02\x21\x01\x12\x02\x90\x03\xe6\x00\xe7\x00\xe8\x00\x11\x00\xe9\x00\x87\x03\x52\x05\x81\x03\xfa\x01\xde\x04\x40\x00\x28\x01\x29\x01\x16\x01\x20\x01\x35\x04\x1e\x01\x21\x01\x73\x00\x1f\x01\xea\x00\x96\x02\x90\xfe\x11\x00\x41\x00\x90\xfe\x22\x01\x61\x03\xeb\x00\xec\x00\x92\xfe\xf5\x01\x11\x02\xed\x00\x53\x05\x12\x02\x21\x02\xf6\x01\xcf\x00\x88\x03\x36\x04\x0b\x02\x20\x01\x4f\x01\xec\x03\x21\x01\xd4\x04\x11\x02\xef\x00\xf0\x00\xf1\x00\x11\x00\x6a\x01\x4b\x02\x22\x01\xf2\x00\x0c\x02\x0d\x02\x90\x00\x2f\x02\x12\x02\xf3\x00\xd2\x00\xf7\x01\xee\x00\x4c\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xb4\x04\x9b\x00\x9c\x00\xed\x03\x4d\x00\x28\x01\x29\x01\x84\x02\x08\x01\x2b\x02\x1e\x01\x6d\x01\x73\x00\x1f\x01\x43\x00\x3b\x01\xf4\x01\x45\x00\x46\x00\x2c\x02\x47\x00\x48\x00\x49\x00\xbd\xfc\x88\x03\xf6\x01\x6e\x01\xcf\x04\x73\x00\x1f\x01\x4a\x00\x4b\x00\x4c\x00\x5d\x03\xf6\x01\x15\x01\x20\x01\x42\x03\xf6\x01\x21\x01\xba\xff\x7a\x02\x4d\x00\xa1\x00\xa2\x00\x11\x00\x07\x01\x7b\x02\x22\x01\xef\x00\xf0\x00\xf1\x00\xa4\x01\xa3\x00\x72\x00\x16\x01\xf2\x00\x73\x00\x74\x00\x90\x00\xf3\x04\x12\x02\xf3\x00\xd2\x00\x22\x01\x90\x02\x49\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x83\x03\x9b\x00\x9c\x00\xce\x00\x12\x02\x7c\x02\x1d\x03\x1e\x03\x16\x01\xd3\x00\xa4\x00\x0f\x00\xd4\x00\xff\xff\xf7\x01\x5f\x05\x4c\x00\xf7\x01\x11\x00\x4c\x00\x7c\x00\x7d\x00\xbb\x01\xe7\x01\xa5\x00\xf2\x04\x4d\x00\x57\x04\x58\x04\x4d\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\x50\x01\x9f\x01\x01\x04\xf6\x01\xb5\x03\x6d\x01\x37\x00\xed\x00\x86\xfd\xa1\x00\xa2\x00\x16\x01\xcf\x00\x51\x01\xba\xff\x52\x01\x53\x01\x59\x04\x5e\x04\xa3\x00\x72\x00\xfa\x01\x3f\x00\x73\x00\x74\x00\x77\x00\xc0\x01\x78\x00\x79\x00\x7a\x00\x80\x03\x7b\x00\xee\x03\xdd\x04\x7e\x00\x7f\x00\x6e\x01\x32\x01\x73\x00\x1f\x01\xca\x02\xce\x00\xf7\x01\x81\x03\x4c\x00\x04\x02\xde\x04\xd3\x00\xa4\x00\x0f\x00\xd4\x00\xf7\x01\x14\x03\x4c\x00\x4d\x00\xf7\x01\x11\x00\x4c\x00\x7c\x00\x7d\x00\x03\x02\x40\x00\xa5\x00\x4d\x00\xc1\x01\x57\x04\x58\x04\x4d\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\x15\x03\x16\x03\x22\x01\x41\x00\xcf\x01\x7f\x00\x37\x04\xed\x00\x47\x01\xd0\x01\x15\x05\xf6\x01\xcf\x00\x86\x01\xd3\x04\x02\x02\x38\x04\x59\x04\x5a\x04\x83\x00\x84\x00\x85\x00\xef\x00\xf0\x00\xa4\x02\x5b\x04\x86\x00\xd4\x04\x81\x00\xf2\x00\x03\x02\x6a\x01\x90\x00\xd9\x03\x5a\x02\xa6\x02\xd2\x00\x48\x01\x49\x01\x4a\x01\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x8c\x00\xfb\x02\x2a\x01\x2b\x01\x8f\x00\xfc\x02\xf7\x01\xc8\x02\x4c\x00\x6c\x01\x09\x02\x35\x05\x34\x05\x6d\x01\x0a\x02\x6d\x01\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x8d\x00\x47\x00\x48\x00\x49\x00\x90\x00\x03\x02\x03\x02\x5b\x02\x0f\x00\x10\x00\x18\x03\x4a\x00\x4b\x00\x4c\x00\xff\xff\x11\x00\xd1\x04\xcd\x04\xce\x04\xa1\x00\xa2\x00\x19\x03\x1a\x03\x4d\x00\xb3\x04\xef\x00\xf0\x00\xa4\x02\x5b\x04\xa3\x00\x72\x00\x7b\x05\xf2\x00\x73\x00\x74\x00\x90\x00\x90\x02\xb4\x04\xa6\x02\xd2\x00\x6d\x01\x7c\x05\xf9\x04\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\xce\x00\x58\x02\x59\x02\x5a\x02\x83\x03\xbf\x01\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x6e\x01\x6f\x01\x73\x00\x1f\x01\xf7\x01\x11\x00\x4c\x00\x7c\x00\x7d\x00\x1d\x03\x1e\x03\xa5\x00\x5e\x05\xcc\x04\xcd\x04\xce\x04\x4d\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\x6e\x01\x71\x03\x73\x00\x1f\x01\x5f\x05\x31\x02\x16\x04\xed\x00\x4c\x00\xa1\x00\xa2\x00\x32\x02\xcf\x00\xaf\x01\x5b\x02\x0f\x00\x10\x00\x22\x01\x4d\x00\xa3\x00\x72\x00\xad\x02\x11\x00\x73\x00\x74\x00\x39\x02\x61\x05\x6e\x01\xcf\x04\x73\x00\x1f\x01\x11\x00\x2c\x01\x29\x01\x34\x03\xac\x01\x4d\x00\x1e\x01\x22\x01\x73\x00\x1f\x01\xce\x00\x46\x03\x47\x03\x83\x00\x84\x00\x85\x00\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x86\x00\x7b\x01\xde\x01\x2e\x02\x47\x00\x11\x00\x4e\x02\x7c\x00\x7d\x00\x2f\x02\x2f\x02\xa5\x00\x20\x01\xff\xff\x22\x01\x21\x01\xdf\x01\xf4\x00\xf5\x00\xf6\x00\xf7\x00\x11\x00\x8c\x00\xef\x01\x22\x01\xff\xff\x4d\x00\x4c\x01\xed\x00\xd0\x04\x0e\x00\x0f\x00\x10\x00\xcf\x00\x6e\x01\xcf\x04\x73\x00\x1f\x01\x11\x00\x81\x01\xe6\x02\x82\x01\xa3\x02\xef\x00\xf0\x00\xa4\x02\xa5\x02\x72\x03\x87\x01\x44\x00\xf2\x00\x64\x00\x46\x00\x90\x00\x47\x00\x67\x00\xa6\x02\xd2\x00\x81\x00\x84\x01\x83\x01\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x83\x00\x84\x00\x85\x00\x22\x01\x0b\xfd\x2d\x05\x72\x00\x86\x00\x37\x00\x73\x00\x74\x00\x87\x00\xef\x01\x7e\x05\x4d\x01\x35\x01\x4e\x01\x89\x00\xd0\x04\x7f\x05\x77\x04\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x56\x01\x8b\x00\x4c\x01\x33\x02\x8c\x00\x8d\x00\x64\x00\x2f\x02\x8f\x00\x90\x00\x67\x00\xef\x01\x35\x03\xae\x02\xab\x02\xac\x02\xa2\x00\x28\x02\x11\x00\x7c\x00\x7d\x00\xef\x00\xf0\x00\xa4\x02\xa5\x02\xa3\x00\x72\x00\x49\x04\xf2\x00\x73\x00\x74\x00\x90\x00\x09\x02\x11\x00\xa6\x02\xd2\x00\x0a\x02\x93\x02\x40\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x4b\x01\xe6\x02\xf0\x03\x95\x02\xce\x00\x41\x00\xd3\x00\xa4\x00\x0f\x00\xd4\x00\xb9\x02\xb2\x01\x64\x00\xb3\x01\xd0\x01\x11\x00\x67\x00\x7c\x00\x7d\x00\xda\x01\x7a\x00\xa5\x00\x7b\x00\x1d\x03\x1e\x03\x61\x04\x96\x02\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xef\x02\xf0\x02\xf1\x02\xf2\x02\xf3\x02\xcb\x01\x10\x00\xaa\x02\xab\x02\xac\x02\xa2\x00\xed\x00\x11\x00\x30\x01\xcc\x01\x7d\x00\xcf\x00\x62\x04\x68\x04\xa3\x00\x72\x00\x88\x04\x89\x04\x73\x00\x74\x00\x8a\x01\x77\x01\x0f\x00\x10\x00\x8b\x01\x07\x01\x8c\x01\x09\x01\x0a\x01\x11\x00\x43\x00\x44\x00\xff\xff\x45\x00\x46\x00\x64\x00\x47\x00\x48\x00\x49\x00\x67\x00\xce\x00\xff\xff\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x4a\x00\x4b\x00\x4c\x00\xef\x01\x1c\x01\x11\x00\xd4\x03\x7c\x00\x7d\x00\xc5\x04\xd5\x03\xa5\x00\x4d\x00\x3b\x02\x7a\x00\x61\x04\x7b\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xe7\x02\x81\x00\xe4\x02\xfc\x01\x1a\x01\x46\x00\x92\xfe\x47\x00\x98\x02\xff\xff\x99\x02\xed\x00\x83\x00\x84\x00\x85\x00\x39\x02\xcf\x00\x62\x04\x63\x04\x86\x00\x19\x01\x11\x00\x26\x04\xcc\x01\x7d\x00\x21\x01\xef\x00\xf0\x00\xa4\x02\x64\x04\xd4\x03\x11\x00\xd7\x02\xf2\x00\x91\x04\xd8\x02\x90\x00\x9a\x02\x18\x03\xa6\x02\xd2\x00\x8c\x00\x8d\x00\x81\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x0b\x05\x0c\x05\x83\x00\x84\x00\x85\x00\x52\x03\x53\x03\x54\x03\x37\x00\x86\x00\xf6\x03\x87\x00\x11\x03\x21\x01\xd4\x03\x2f\x05\xe8\x02\x89\x00\x4e\x05\x11\x00\x0f\x02\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x98\xfe\x8b\x00\x56\x01\x98\xfe\x0f\x03\x8e\x00\x8c\x00\x8d\x00\x0b\x05\x59\x05\x8f\x00\x90\x00\x50\x05\xcd\x04\xce\x04\xa1\x00\xa2\x00\x41\x01\x42\x01\x43\x01\x44\x01\xef\x00\xf0\x00\xa4\x02\x64\x04\xa3\x00\x72\x00\x64\x00\xf2\x00\x73\x00\x74\x00\x90\x00\x87\x02\xff\x02\xa6\x02\xd2\x00\x01\x02\xff\x01\x40\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\xce\x00\xfe\x01\xff\x01\xc0\x02\x10\x00\x41\x00\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x11\x00\x3e\x03\xcc\x01\x7d\x00\x46\x00\x11\x00\x47\x00\x7c\x00\x7d\x00\x07\x03\x90\x01\xa5\x00\x91\x01\xf7\x02\x57\x04\x58\x04\xeb\x02\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xb5\x02\x0f\x00\x10\x00\xb2\x02\x0f\x00\x10\x00\xfc\x01\xed\x00\x11\x00\xa1\x00\xa2\x00\x11\x00\xcf\x00\xe3\x02\xce\x01\x9f\x01\x7a\x00\x04\x05\x7b\x00\xa3\x00\x72\x00\xcf\x01\x7f\x00\x73\x00\x74\x00\xe2\x02\xd0\x01\x6e\x01\xcf\x04\x73\x00\x1f\x01\xdf\x02\xaf\x02\x0f\x00\x10\x00\x43\x00\x44\x00\xe1\x02\x45\x00\x46\x00\x11\x00\x47\x00\x48\x00\x49\x00\x0d\x03\xd4\x02\xd5\x02\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x4a\x00\x4b\x00\x4c\x00\xe0\x02\x81\x01\x11\x00\x82\x01\x7c\x00\x7d\x00\xdb\x02\x2f\x05\xa5\x00\x4d\x00\x46\x00\x22\x01\x47\x00\xd9\x02\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf1\x01\x59\x01\xef\x01\xd3\x02\xd4\x02\xd5\x02\x00\x05\xfe\x04\xd0\x04\x86\x01\x87\x01\x44\x00\xca\x02\x74\x02\x46\x00\x75\x02\x47\x00\xce\x01\x9f\x01\x7a\x00\xcb\x02\x7b\x00\xef\x00\xf0\x00\xa4\x02\x5b\x04\x88\x01\xce\x00\x4c\x00\xf2\x00\xc7\x02\x1d\x04\x90\x00\x1e\x04\xc0\x02\xa6\x02\xd2\x00\xbf\x02\x4d\x00\x40\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x61\x04\x74\x03\x72\x01\x73\x01\x74\x01\x41\x00\x75\x01\xe2\x03\xe3\x03\xe4\x03\x1e\x01\xb9\x01\x73\x00\x1f\x01\xce\x01\x9f\x01\x7a\x00\xed\x00\x7b\x00\x37\x00\x7e\x01\xb5\x01\xcf\x00\x0c\x05\xd4\x01\x4d\x02\xd5\x01\xe8\x02\x15\x04\xd6\x01\x16\x04\xc5\x02\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x20\x01\x7e\x01\x7f\x01\x21\x01\xa1\x00\xa2\x00\x7d\x01\x79\x01\x57\x02\x11\x00\xf7\xfc\x81\x01\x22\x01\x82\x01\xa3\x00\x72\x00\x4c\x02\xd9\x01\x73\x00\x74\x00\x21\x01\x47\x03\x48\x03\x49\x03\xbd\x02\xbb\x01\x11\x00\xe6\x03\x7c\x00\x7d\x00\x43\x00\x44\x00\xbc\x02\xd0\x03\x46\x00\xd1\x03\x47\x00\x69\x02\x40\x00\x07\x04\x08\x04\x09\x04\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x4a\x00\x40\x00\x4c\x00\x7b\x01\x79\x01\x11\x00\x41\x00\x7c\x00\x7d\x00\x78\x01\x79\x01\xa5\x00\x4d\x00\xbb\x02\x6d\x04\x41\x00\x6e\x04\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xec\x01\xef\x00\xf0\x00\xa4\x02\x64\x04\xce\x00\x3b\x02\x7a\x00\xf2\x00\x7b\x00\x4d\x04\x90\x00\x4e\x04\xb9\x02\xa6\x02\xd2\x00\xf0\x04\xd0\x01\xf1\x04\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x7b\x04\x08\x04\x09\x04\x6e\x04\x08\x04\x09\x04\xc2\x04\x08\x04\x09\x04\x8e\x05\x08\x04\x09\x04\x93\x05\x08\x04\x09\x04\xe4\x04\xed\x00\xe5\x04\x8e\x02\x43\x00\x44\x00\xcf\x00\x45\x00\x46\x00\x8d\x02\x47\x00\x48\x00\x49\x00\x43\x00\x44\x00\xe9\x04\xa3\x04\x46\x00\xa4\x04\x47\x00\x4a\x00\x4b\x00\x4c\x00\x44\x01\x45\x01\xa1\x00\xa2\x00\x8f\x02\xf0\x04\x4a\x00\xf1\x04\x4c\x00\x4d\x00\x2d\x01\x2e\x01\xa3\x00\x72\x00\xfc\x02\xfd\x02\x73\x00\x74\x00\x4d\x00\x87\x00\x6d\x03\x6e\x03\x60\x02\x35\x01\xb9\x01\x89\x00\x90\x02\x49\x00\x88\x02\xbd\xfc\x7e\x01\x10\x04\xfa\x03\xfb\x03\x8b\x00\x80\x02\x56\x00\x5f\x04\x54\x03\x7d\x02\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x86\x02\x57\x00\x79\x02\x58\x00\x59\x00\x11\x00\x78\x02\x7c\x00\x7d\x00\x07\x01\x5b\x00\xa5\x00\x65\x05\x66\x05\x6a\x02\xfd\x04\xfe\x04\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xef\x00\xf0\x00\xa4\x02\xa5\x02\xce\x00\x71\x02\x70\x02\xf2\x00\x6f\x02\x6e\x02\x90\x00\x65\x00\x66\x00\xa6\x02\xd2\x00\x68\x00\x69\x00\x69\x02\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x68\x02\xbb\x01\x60\x02\x50\x02\x4f\x02\x4d\x02\x4c\x02\x4a\x02\x49\x02\x48\x02\x39\x02\x38\x02\x35\x02\x2a\x02\x34\x02\x30\x02\xed\x00\x0e\x01\x2d\x02\x01\x02\xc8\x03\xcf\x00\xb8\x02\x72\x01\x73\x01\x74\x01\xc7\x03\x75\x01\x0f\x02\x37\x00\xe8\x04\x1e\x01\xc6\x03\x73\x00\x1f\x01\xc3\x03\xbc\x03\xe8\x02\xbd\x03\xbb\x03\xa1\x00\xa2\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\xd8\xfc\xf6\xfc\xe1\xfc\xdf\xfc\xa3\x00\x72\x00\x1d\x01\xe0\xfc\x73\x00\x74\x00\x1e\x01\x20\x01\x73\x00\x1f\x01\x21\x01\xf5\xfc\xd9\xfc\xda\xfc\x3b\x02\x7a\x00\x11\x00\x7b\x00\xba\x03\x22\x01\x37\x02\xb9\x02\xb9\x03\xd4\x04\xb8\x03\xd0\x01\xb7\x03\xb4\x03\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x20\x01\xb3\x03\x40\x00\x21\x01\xb2\x03\x11\x00\xab\x03\x7c\x00\x7d\x00\x11\x00\xa1\x03\xa5\x00\x22\x01\x6d\x01\xc4\x02\x8f\x03\x41\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xef\x00\xf0\x00\xa4\x02\xa5\x02\xce\x00\x30\x02\x8d\x03\xf2\x00\x8b\x03\x8e\x03\x90\x00\x84\x03\x7f\x03\xa6\x02\xd2\x00\x7e\x03\x7d\x03\x7b\x03\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x7a\x03\x7c\x03\x79\x03\x78\x03\x37\x00\x77\x03\x74\x03\x71\x03\x70\x03\x57\x03\x6a\x01\x62\x03\xd5\x04\x5f\x03\x0a\xfd\x52\x03\xed\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\xcf\x00\x50\x03\x4e\x03\xd4\x01\x44\x03\xd5\x01\x2e\x03\x23\x03\xd6\x01\x43\x00\x44\x00\xd7\x01\x45\x00\x46\x00\x8b\x00\x47\x00\x48\x00\x49\x00\x30\x01\xa1\x00\xa2\x00\x22\x03\x29\x03\xd8\x01\x21\x03\x4a\x00\x4b\x00\x4c\x00\x0e\x01\xa3\x00\x72\x00\xf0\x03\xd9\x01\x73\x00\x74\x00\x21\x01\x81\x00\x4d\x00\x40\x00\xda\x01\x7a\x00\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x83\x00\x84\x00\x85\x00\x08\x05\x39\x04\x41\x00\xcd\x03\x86\x00\x3b\x04\x34\x04\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x2e\x04\x2c\x04\x2b\x04\x28\x04\x6c\x01\x11\x00\x01\xfd\x7c\x00\x7d\x00\x2a\x04\x6d\x01\xa5\x00\x00\xfd\x02\xfd\x26\x04\x8c\x00\x8d\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xef\x00\xf0\x00\xa4\x02\xf9\x03\x25\x04\x23\x04\x13\x04\xf2\x00\x19\x04\x5d\x03\x90\x00\x0d\x04\x0e\x04\xa6\x02\xd2\x00\x0b\x04\x07\x04\x03\x04\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\xa7\x02\xa8\x02\xa9\x02\x03\x05\x01\x04\x37\x00\xc4\x02\xf5\x03\x43\x00\x44\x00\xff\x03\x45\x00\x46\x00\xe8\x02\x47\x00\x48\x00\x49\x00\x6a\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\xe0\x03\xf0\x03\x4a\x00\x4b\x00\x4c\x00\xe7\x03\x75\x03\x74\x01\xe1\x03\x75\x01\x36\x02\xd8\x03\x08\x01\x1e\x01\x4d\x00\x73\x00\x1f\x01\x6d\x05\xd7\x03\xcd\x03\xa1\x04\xa1\x00\xa2\x00\x99\x04\x93\x04\x90\x04\x68\x02\x08\x01\x07\x01\x5d\x03\x8e\x04\xa3\x00\x72\x00\xbb\x01\x8a\x04\x73\x00\x74\x00\x41\x04\x40\x00\x20\x01\x84\x03\x37\x00\x21\x01\x82\x04\x81\x04\x80\x04\x0d\x04\x7f\x04\x11\x00\xe8\x02\x0b\x04\x22\x01\x41\x00\x0b\x04\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x07\x01\xd3\x00\xa4\x00\x0f\x00\xd4\x00\x70\x01\x71\x01\x72\x01\x73\x01\x74\x01\x11\x00\x75\x01\x7c\x00\x7d\x00\x57\x04\x1e\x01\xa5\x00\x73\x00\x1f\x01\x37\x00\x51\x04\x4c\x04\xf4\x00\xf5\x00\xf6\x00\xf7\x00\x48\x04\xe8\x02\xcc\x02\x45\x04\x47\x04\x44\x04\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x43\x04\x42\x04\x40\x00\x41\x04\x21\x03\x20\x01\xec\x04\xeb\x04\x21\x01\xe7\x04\xe6\x04\xe0\x04\xdb\x04\x4a\x01\x11\x00\x08\x01\x41\x00\x22\x01\xc5\x04\x43\x00\x44\x00\x0b\x04\x45\x00\x46\x00\xbc\x04\x47\x00\x48\x00\x49\x00\x81\x00\x55\x01\xac\xfe\xbb\x04\x25\x05\xac\xfe\x33\x05\x4a\x00\x4b\x00\x4c\x00\x40\x00\x83\x00\x84\x00\x85\x00\x37\x00\xb1\x04\x1c\x01\x27\x05\x86\x00\x4d\x00\x4d\x01\x20\x05\x4e\x01\x1f\x05\x41\x00\x1e\x05\x14\x05\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x11\x05\x15\x05\x94\x01\x72\x00\x13\x05\x56\x01\x73\x00\x74\x00\x10\x05\x8c\x00\x8d\x00\x0f\x05\x0e\x05\x8f\x00\x90\x00\xf6\x04\x59\x01\x64\x05\x43\x00\x44\x00\x52\x03\x45\x00\x46\x00\x6a\x05\x47\x00\x48\x00\x49\x00\x63\x05\x66\x03\x5d\x05\x4d\x05\x95\x01\x0f\x00\x10\x00\x4a\x00\x4b\x00\x4c\x00\x08\x01\x40\x00\x11\x00\x4e\x05\x7c\x00\x7d\x00\x49\x05\x40\x05\x3f\x05\x4d\x00\x5b\x05\x37\x05\x80\x05\x3e\x05\x76\x05\x41\x00\x7d\x05\x43\x00\x44\x00\x3d\x05\x45\x00\x46\x00\x81\x05\x47\x00\x48\x00\x49\x00\xcd\x03\x07\x01\x72\x05\x59\xfe\x6d\x05\x0d\x04\x0b\x04\x4a\x00\x4b\x00\x4c\x00\x92\x05\xc6\x03\x8d\x05\xcd\x03\x37\x00\x99\x05\x98\x05\x96\x05\x0b\x04\x4d\x00\x67\x03\x93\x05\x68\x03\x9b\x05\x0c\x01\xcd\x01\xbc\x01\x3c\x00\x3d\x00\x3e\x00\x3f\x00\xb4\x01\xb0\x01\x37\x00\x8e\x01\x84\x01\x56\x01\x3f\x01\x35\x01\x67\x03\x1a\x01\x68\x03\x13\x03\x0f\x03\x12\x03\x11\x03\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x43\x00\x44\x00\x07\x03\x45\x00\x46\x00\x01\x03\x47\x00\x48\x00\x49\x00\x0a\x03\xf3\x02\xcb\x02\xed\x02\xd9\x02\xe3\x01\x84\x02\x4a\x00\x4b\x00\x4c\x00\x40\x00\xbd\x02\x72\x02\x25\x03\x29\x01\x22\x02\x0a\x02\x66\x02\x1e\x01\x4d\x00\x73\x00\x1f\x01\xcd\x02\x9a\x02\x41\x00\x07\x02\x37\x00\xca\x03\x0f\x02\x40\x00\x55\x02\x9b\x02\xce\x02\xc9\x03\x3b\x00\x9d\x02\x18\x03\xc8\x03\x64\x02\xcf\x02\x3d\x00\x3e\x00\x3f\x00\x41\x00\x20\x01\xae\x03\x5f\x03\x21\x01\x5f\x03\x55\x03\xb5\x03\x50\x03\x4e\x03\x11\x00\x8f\x03\x85\x03\x22\x01\x84\x03\x4c\x03\x44\x03\x34\x03\x9a\x02\x29\x03\x2c\x03\x37\x00\x1f\x03\x27\x03\x1e\x03\x1b\x03\x9b\x02\x9c\x02\x3f\x04\x3e\x04\x9d\x02\x3b\x04\x3d\x04\x39\x04\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x40\x00\x3c\x04\x2c\x04\x1e\x04\x43\x00\x44\x00\x21\x04\x45\x00\x46\x00\x1b\x04\x47\x00\x48\x00\x49\x00\x13\x04\x41\x00\x0b\x04\x0f\x04\x11\x04\xf5\x03\xee\x03\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\xe7\x03\x45\x00\x46\x00\xce\x03\x47\x00\x48\x00\x49\x00\x4d\x00\xcd\x03\xcb\x03\x8e\x04\x64\x02\x8c\x04\x40\x00\x4a\x00\x4b\x00\x4c\x00\x7c\x04\x77\x04\x55\x04\x60\x04\x33\x03\xf1\x04\xee\x04\x37\x00\xed\x04\x4d\x00\x41\x00\xe2\x04\x9b\x02\x9c\x02\xd0\x02\x45\x04\x9d\x02\xe1\x04\x13\x00\xde\x04\x9e\x02\x3d\x00\x3e\x00\x3f\x00\xd9\x04\xe0\x04\x14\x00\xdb\x04\xc3\x04\xc9\x04\xca\x04\xb1\x04\xb9\x04\x43\x00\x44\x00\x31\x05\x45\x00\x46\x00\x15\x00\x47\x00\x48\x00\x49\x00\xa1\x04\x30\x05\x17\x00\x18\x00\x19\x00\x25\x05\x22\x05\x4a\x00\x4b\x00\x4c\x00\x9f\x02\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x21\x05\x09\x05\x24\x00\x4d\x00\x40\x00\x11\x05\x02\x05\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x43\x00\x44\x00\xa0\x02\x45\x00\x46\x00\x41\x00\x47\x00\x48\x00\x49\x00\xf9\x04\xf4\x04\x6a\x05\x60\x05\x81\x00\x64\x05\x5f\x05\x4a\x00\x4b\x00\x4c\x00\x5a\x05\xd2\x01\x47\x05\xd3\x01\x57\x05\x83\x00\x84\x00\x85\x00\xf7\x03\x4d\x00\x77\x05\x37\x00\x86\x00\x46\x05\x76\x05\x87\x05\x9b\x02\x9c\x02\x8f\x05\x8b\x05\x9d\x02\xa0\x02\x94\x05\x6c\x01\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x9f\x02\x6d\x01\x9b\x05\x00\x00\x85\x05\x96\x05\x8c\x00\x8d\x00\x00\x00\x99\x05\x8f\x00\x90\x00\x00\x00\x18\x02\x19\x02\x8b\x05\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x1a\x02\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x40\x00\xe9\x01\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x00\x00\x4f\x04\x4d\x00\x00\x00\x37\x00\x5b\x00\x00\x00\x41\x00\x00\x00\x9b\x02\x9c\x02\x00\x00\x00\x00\x9d\x02\xa0\x02\x00\x00\x92\x02\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x6d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x65\x00\x66\x00\x00\x00\x00\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe7\x04\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9b\x02\x9c\x02\x9f\x02\x00\x00\x9d\x02\x00\x00\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x41\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x40\x00\xa7\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x02\x59\x05\x00\x00\x41\x00\x37\x00\x00\x00\x00\x00\x9f\x02\x00\x00\x9b\x02\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x75\x02\x76\x02\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x9f\x02\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\xa0\x02\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x41\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x51\x05\x4d\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9b\x02\x9c\x02\x00\x00\x00\x00\x9d\x02\xa0\x02\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x37\x00\x00\x00\x9f\x02\x00\x00\x00\x00\x00\x00\xc0\x04\x00\x00\xc1\x04\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x16\x05\x4d\x00\x41\x00\x17\x05\x18\x05\x19\x05\x2a\x05\x40\x00\x1a\x05\x3f\x00\x00\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x2b\x05\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x41\x00\x00\x00\x37\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1b\x05\x00\x00\x00\x00\x00\x00\x73\x05\x19\x05\x00\x00\x00\x00\x1a\x05\x3f\x00\x00\x00\x00\x00\x37\x00\x00\x00\x9f\x02\x00\x00\x8c\x00\x2c\x05\x40\x00\x00\x00\x8f\x00\x2d\x05\x00\x00\x00\x00\x4b\x05\x00\x00\x00\x00\x1a\x05\x3f\x00\x00\x00\x74\x05\x00\x00\x41\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x4d\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x81\x00\xa0\x02\x49\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x41\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x01\x4a\x00\x4b\x00\x4c\x00\x8c\x00\x8d\x00\x00\x00\x00\x00\x8f\x00\x90\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x1c\x05\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x37\x00\x1c\x05\x00\x00\x00\x00\x1e\x02\xf2\x03\xce\x02\x4d\x00\x3b\x00\x9d\x02\x00\x00\x00\x00\x81\x00\xcf\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x1c\x05\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x37\x00\x86\x00\x00\x00\x00\x00\x1d\x02\xf1\x03\xce\x02\x00\x00\x3b\x00\x9d\x02\x00\x00\x00\x00\x6c\x01\xcf\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x6d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x8c\x00\x8d\x00\x00\x00\x40\x00\x8f\x00\x90\x00\x37\x00\x00\x00\x00\x00\x00\x00\xc4\x03\x6a\x04\xce\x02\x00\x00\x3b\x00\x9d\x02\x00\x00\x41\x00\x00\x00\xcf\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\xc6\x04\x50\x01\x40\x03\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x41\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\xc5\x01\xc7\x04\x52\x01\x53\x01\x00\x00\x00\x00\x00\x00\xd0\x02\x00\x00\x40\x00\x00\x00\x00\x00\x77\x00\x00\x00\x78\x00\x79\x00\x7a\x00\x00\x00\x7b\x00\x00\x00\x00\x00\x7e\x00\x7f\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\xd0\x02\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\xd0\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x37\x00\x00\x00\x00\x00\xc6\x04\x00\x00\x40\x03\x9c\x02\x00\x00\x4d\x00\x9d\x02\x00\x00\x00\x00\x81\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x4f\x05\x00\x00\xa0\x02\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x37\x00\x86\x00\x00\x00\x41\x03\x00\x00\x40\x03\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x56\x01\x00\x00\x00\x00\x00\x00\x8c\x00\x8d\x00\x00\x00\x40\x00\x8f\x00\x90\x00\x37\x00\x00\x00\x00\x00\x3f\x03\x00\x00\x40\x03\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x41\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x50\x01\xf2\x03\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x41\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x51\x01\x00\x00\x52\x01\x53\x01\x00\x00\x00\x00\x00\x00\x9f\x02\x00\x00\x40\x00\x00\x00\x00\x00\x77\x00\x00\x00\x78\x00\x79\x00\x7a\x00\x00\x00\x7b\x00\x00\x00\x00\x00\x7e\x00\x7f\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf1\x03\x9c\x02\x00\x00\x4d\x00\x9d\x02\x00\x00\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x04\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x00\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6a\x04\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x41\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x50\x01\x6b\x04\x9c\x02\x00\x00\x00\x00\x9d\x02\x00\x00\x41\x00\x00\x00\x9e\x02\x3d\x00\x3e\x00\x3f\x00\xc8\x02\x00\x00\x52\x01\x53\x01\x00\x00\x00\x00\x00\x00\x9f\x02\x00\x00\x40\x00\x00\x00\x00\x00\x77\x00\x00\x00\x78\x00\x79\x00\x7a\x00\x00\x00\x7b\x00\x00\x00\x00\x00\x7e\x00\x7f\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x9f\x02\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x3a\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\xe0\x01\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x00\x00\x00\x00\xe1\x01\xe2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x37\x00\x00\x00\xe5\x01\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x81\x00\x55\x01\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\x40\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x56\x01\x00\x00\x00\x00\x00\x00\x8c\x00\x8d\x00\x00\x00\x00\x00\x8f\x00\x90\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3b\x02\x7a\x00\x4d\x00\x7b\x00\x00\x00\x00\x00\xcf\x01\x7f\x00\x50\x01\x00\x00\x00\x00\xd0\x01\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\xc5\x01\x00\x00\x52\x01\x53\x01\x42\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x77\x00\x00\x00\x78\x00\x79\x00\x7a\x00\x00\x00\x7b\x00\x4d\x00\x00\x00\x7e\x00\x7f\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\xe3\x01\x47\x00\xe6\x01\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\xe5\x01\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\xe7\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x02\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\xe3\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x02\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x13\x00\x41\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x14\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\xb1\x02\x00\x00\x00\x00\x00\x00\x40\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x42\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x41\x00\x47\x00\xe6\x01\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x70\x05\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\xe7\x01\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x4a\x00\x4b\x00\x4c\x00\x18\x02\x19\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x1a\x02\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x02\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x1a\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x03\x00\x00\x00\x00\xff\x03\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x03\x40\x00\x00\x00\xfd\x03\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x03\x40\x00\x00\x00\xbf\x04\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x02\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\x55\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xdc\x02\x46\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x45\x02\x46\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xc1\x03\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xc0\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\xbe\x03\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x03\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xbd\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x44\x02\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xd8\x03\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x23\x04\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x38\x00\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\xea\x01\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x91\x01\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x54\x05\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x90\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x1c\x02\x37\x00\x00\x00\x23\x04\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa8\x01\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\xa1\x00\xa2\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x40\x00\x00\x00\x20\x04\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x11\x00\x19\x04\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x90\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\xa5\x01\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x05\x04\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\xd2\x03\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\xa1\x00\xa2\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x40\x00\x00\x00\x51\x04\x37\x00\x00\x00\xfa\x04\x00\x00\x39\x00\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\x1b\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x90\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc1\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x56\x05\x37\x00\x00\x00\x00\x00\x00\x00\x1e\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x1d\x02\x00\x00\x3a\x00\x00\x00\x3b\x00\xa1\x00\xa2\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x40\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\xc4\x03\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x41\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x42\x00\x00\x00\x40\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x37\x00\x00\x00\x00\x00\x00\x00\xd3\x03\x00\x00\x3a\x00\x00\x00\x3b\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\xf6\x04\x00\x00\x3a\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\xe6\x02\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdd\x02\x00\x00\x40\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x37\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdb\x02\x81\x00\xc7\x01\x42\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x41\x00\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\xc8\x01\xc9\x01\xca\x01\xcb\x01\x86\x00\x00\x00\x40\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x42\x00\x00\x00\x00\x00\x41\x00\x00\x00\x56\x01\x4a\x00\x4b\x00\x4c\x00\x8c\x00\x8d\x00\x00\x00\x00\x00\x8f\x00\x90\x00\x40\x00\x00\x00\x00\x00\x4d\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x1f\x02\x47\x00\x48\x00\x49\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x57\x03\x47\x00\x48\x00\x49\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x40\x00\x00\x00\x4d\x00\x00\x00\x00\x00\x0e\x04\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x41\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf3\x03\x00\x00\x40\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7d\x04\x00\x00\x40\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x52\x04\x47\x00\x48\x00\x49\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x00\x00\x07\x05\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x05\x00\x00\x40\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x81\x00\x07\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x37\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x4a\x05\x86\x00\x40\x00\x00\x00\x00\x00\x3a\x01\x3d\x00\x3e\x00\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\x37\x00\x56\x01\x00\x00\x40\x00\x00\x00\x8c\x00\x8d\x00\x00\x00\x00\x00\x8f\x00\x90\x00\x00\x00\x00\x00\x89\x03\x3d\x00\x3e\x00\x3f\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x43\x00\x44\x00\x00\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x44\x00\x4d\x00\x45\x00\x46\x00\x00\x00\x47\x00\x48\x00\x49\x00\x00\x00\x00\x00\x11\x02\xa7\x00\x13\x00\xa8\x00\x00\x00\x4a\x00\x4b\x00\x4c\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x02\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\xa8\x03\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\xfd\x00\xd9\x00\x00\x00\xfe\x00\x00\x00\x15\x00\x00\x00\xff\x00\x00\x00\x16\x00\x00\x01\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x02\x01\xb0\x00\xde\x00\xb2\x00\x03\x01\x04\x01\x00\x00\x00\x00\x05\x01\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x66\x04\x67\x04\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x68\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x5d\x04\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\xfe\x00\x00\x00\x15\x00\x00\x00\x5e\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x66\x04\x67\x04\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x68\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x5d\x04\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\xfe\x00\x00\x00\x15\x00\x00\x00\x5e\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x01\x01\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x07\x01\x08\x01\x09\x01\x0a\x01\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x6a\x01\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x6b\x01\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x6c\x01\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x6d\x01\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x6a\x01\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x9f\x01\xba\x00\x00\x00\x00\x00\x6d\x01\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x6a\x01\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x6b\x01\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x6c\x01\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x6d\x01\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x4b\x02\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x2f\x02\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x4e\x02\xba\x00\x00\x00\x00\x00\x2f\x02\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\xa4\x01\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\xc4\x02\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x2f\x02\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\x00\x00\xd8\xfd\x00\x00\xd8\xfd\x00\x00\x00\x00\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\x00\x00\xd8\xfd\x00\x00\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd8\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\x00\x00\xd7\xfd\x00\x00\xd7\xfd\x00\x00\x00\x00\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\x00\x00\x00\x00\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\x00\x00\xd7\xfd\x00\x00\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xd7\xfd\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\xda\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdb\x00\xdc\x00\xdd\x00\x00\x00\x00\x00\xb0\x00\xde\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xe1\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x6e\x01\xbb\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x03\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\xa8\x03\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\xae\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\xbb\x01\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbc\x01\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\xae\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x9e\x03\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\xa8\x03\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\xae\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x9e\x03\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\xeb\x03\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\xb1\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x00\x00\x00\xb2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\xab\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc3\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\xaf\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc3\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\xab\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x00\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\xa7\x00\x13\x00\xa8\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\x14\x00\xaa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xac\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xad\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\xa7\x00\x13\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x14\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x94\x03\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\xa7\x00\x13\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x14\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\xb7\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x00\x00\xb9\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x00\x00\x6a\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\x00\x00\x4f\x00\x13\x00\x00\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\x00\x00\xcb\x00\x14\x00\x6d\x00\x6e\x00\xcc\x00\xcd\x00\xce\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x63\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x01\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\xea\x01\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x01\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\xe5\x01\x00\x00\x00\x00\x00\x00\x6d\x01\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x3e\x02\x3f\x02\x40\x02\x00\x00\x00\x00\x00\x00\x00\x00\x41\x02\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x6c\x01\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x01\x61\x00\x62\x00\x63\x00\x64\x00\x42\x02\x43\x02\x00\x00\x67\x00\x68\x00\x44\x02\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xa2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\xc9\x04\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\xd2\x02\x07\x01\x00\x00\x14\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\xec\x01\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x01\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x3e\x01\x3f\x01\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\xa7\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xd2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x75\x02\xa1\x03\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\xb3\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xa2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\xaf\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xd2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\xa6\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xa2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\xa4\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xd2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\x59\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xa2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x04\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\xd8\x04\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x1c\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xa2\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x14\x00\x00\x00\x00\x00\x0c\x03\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x0b\x03\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x02\x05\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\xc1\x01\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x05\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x71\x02\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x5e\x02\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x50\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x56\x05\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x23\x03\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x88\xfe\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\xa4\x00\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x01\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x01\x00\x00\x9b\x00\x9c\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x98\x01\x0f\x00\x10\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x11\x00\x60\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x6a\x03\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x01\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x6a\x03\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x01\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\xea\x02\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x01\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5c\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x00\x00\x67\x00\x68\x00\x69\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x4f\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x00\x00\x15\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x13\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x14\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x5f\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf3\x01\x63\x00\x64\x00\x00\x00\x00\x00\x00\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x28\x02\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6e\x00\x2c\x00\x00\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x3d\x03\x17\x00\x18\x00\x19\x00\x3a\x03\x3b\x03\x3c\x03\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x03\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\xb7\x04\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x03\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x02\x19\x02\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x1a\x02\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x02\x19\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1a\x02\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x00\x00\x00\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x13\x00\x00\x00\x88\x00\x00\x00\x89\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x8a\x00\x00\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x2d\x00\x8e\x00\x8f\x00\x90\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x84\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdc\x01\xc2\x02\x13\x00\x00\x00\xdd\x01\x00\x00\x89\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\xde\x01\x00\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x00\x00\x8e\x00\x00\x00\x90\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xac\x04\x00\x00\x00\x00\x15\x00\x00\x00\xad\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\xae\x04\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\xac\x04\x00\x00\x00\x00\x15\x00\x00\x00\xad\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\xae\x04\xaf\x04\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xb0\x04\x00\x00\x00\x00\x2c\x00\x64\x00\x13\x00\x00\x00\x2d\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\xaf\x04\x13\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x14\x00\x2c\x00\x64\x00\x00\x00\x00\x00\x2d\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\xad\x04\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x87\x00\x00\x00\x00\x00\x00\x00\x97\x01\x13\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x00\x00\x3c\x05\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\xaf\x04\x13\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x14\x00\x2c\x00\x64\x00\x00\x00\x00\x00\x2d\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\xdc\x01\x13\x00\x00\x00\x00\x00\xdd\x01\x00\x00\x89\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x2d\x00\x8e\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x8a\x01\x13\x00\x00\x00\x00\x00\x8b\x01\x00\x00\x8c\x01\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x00\x64\x00\x00\x00\x00\x00\x00\x00\x67\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x00\x00\x00\x00\x63\x00\x64\x00\x00\x00\x00\x00\x00\x00\x67\x00\x5d\x02\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x2b\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x90\x00\x5a\x01\x5b\x01\x2d\x00\x93\x00\x94\x00\x81\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x83\x00\x84\x00\x85\x00\x5c\x01\x5d\x01\x00\x00\x00\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x77\x01\x6c\x01\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x01\x00\x00\x00\x00\x2c\x00\x8b\x00\x8c\x00\x8d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x63\x01\x9f\x01\x65\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x66\x01\x7f\x00\xa5\x00\x00\x00\x00\x00\x67\x01\x13\x00\x68\x01\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x14\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x15\x00\x00\x00\x5c\x01\x5d\x01\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x63\x01\x64\x01\x65\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x66\x01\x7f\x00\xa5\x00\x00\x00\x63\x00\x67\x01\x00\x00\x68\x01\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x01\x9a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x13\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x14\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x24\x01\x00\x00\x9d\x01\x15\x00\x68\x01\x25\x01\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x26\x01\x13\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x87\x00\x00\x00\x24\x00\x00\x00\x77\x01\x13\x00\x89\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x35\x01\x13\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x87\x00\x00\x00\x24\x00\x00\x00\x26\x01\x13\x00\x89\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x77\x01\x13\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x87\x00\x00\x00\x24\x00\x00\x00\x26\x01\x13\x00\x89\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x2c\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x13\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x2c\x00\x8b\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x02\x19\x02\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\xff\x14\x00\x00\x00\x00\x00\x03\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\xfa\x02\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xc0\x02\x00\x00\x24\x00\x2c\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x32\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x16\x00\x00\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x13\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x32\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x17\x00\x18\x00\x19\x00\x51\x00\x52\x00\x53\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf9\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\xe1\x00\x92\x00\x63\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x03\xa3\x03\xa4\x03\x00\x00\x00\x00\xf9\x01\x00\x00\x00\x00\xa5\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x01\xa4\x00\x0f\x00\x10\x00\xa1\x01\xa2\x01\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\xa6\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7d\x02\x00\x00\x00\x00\x7e\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7d\x02\x00\x00\x00\x00\x94\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9f\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x96\x03\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6c\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x5a\x01\x5b\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\xda\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x60\x01\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x62\x01\x9b\x01\x00\x00\x9c\x01\x11\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xa5\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x98\x03\x99\x03\x9a\x03\x9b\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9c\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x86\x04\x9a\x03\x9b\x03\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9c\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0a\x01\x0b\x01\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9e\x00\x00\x00\x9f\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x6c\x02\x00\x00\x00\x00\x6b\x02\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x6a\x02\x00\x00\x00\x00\x6b\x02\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x61\x02\x62\x02\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\xa8\x03\xa3\x03\xa4\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa5\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x58\x03\x62\x02\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\xe1\x03\xa3\x03\xa4\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa5\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xb6\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\xb7\x01\xb8\x01\xb9\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xde\x03\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x84\x04\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x91\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdc\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x8a\x04\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\xa5\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\xe2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x2f\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe1\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x2e\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe4\x00\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xd3\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xc4\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xc3\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xbd\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x93\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x8d\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x8c\x01\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x5d\x02\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x53\x02\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x52\x02\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x51\x02\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x50\x02\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xb0\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xaf\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xab\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x9e\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x59\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xf8\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe9\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xe8\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xdd\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xdb\x03\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x8b\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x83\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x69\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xec\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xbe\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xbd\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\xbc\x04\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x20\x05\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x49\x05\x92\x00\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x00\x00\x92\x01\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x00\x00\xc5\x02\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x00\x00\x32\x04\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x90\x00\x00\x00\xd8\x04\x00\x00\x93\x00\x94\x00\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x90\x00\x00\x00\x73\x00\x74\x00\x93\x00\x56\x02\x00\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x00\x00\x9b\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x91\x03\x00\x00\x9b\x00\x9c\x00\x11\x00\x92\x03\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x72\x00\x00\x00\x00\x00\x73\x00\x74\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x98\x01\x0f\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x7c\x00\x7d\x00\x00\x00\x00\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
2371
2372happyReduceArr = Happy_Data_Array.array (13, 834) [
2373	(13 , happyReduce_13),
2374	(14 , happyReduce_14),
2375	(15 , happyReduce_15),
2376	(16 , happyReduce_16),
2377	(17 , happyReduce_17),
2378	(18 , happyReduce_18),
2379	(19 , happyReduce_19),
2380	(20 , happyReduce_20),
2381	(21 , happyReduce_21),
2382	(22 , happyReduce_22),
2383	(23 , happyReduce_23),
2384	(24 , happyReduce_24),
2385	(25 , happyReduce_25),
2386	(26 , happyReduce_26),
2387	(27 , happyReduce_27),
2388	(28 , happyReduce_28),
2389	(29 , happyReduce_29),
2390	(30 , happyReduce_30),
2391	(31 , happyReduce_31),
2392	(32 , happyReduce_32),
2393	(33 , happyReduce_33),
2394	(34 , happyReduce_34),
2395	(35 , happyReduce_35),
2396	(36 , happyReduce_36),
2397	(37 , happyReduce_37),
2398	(38 , happyReduce_38),
2399	(39 , happyReduce_39),
2400	(40 , happyReduce_40),
2401	(41 , happyReduce_41),
2402	(42 , happyReduce_42),
2403	(43 , happyReduce_43),
2404	(44 , happyReduce_44),
2405	(45 , happyReduce_45),
2406	(46 , happyReduce_46),
2407	(47 , happyReduce_47),
2408	(48 , happyReduce_48),
2409	(49 , happyReduce_49),
2410	(50 , happyReduce_50),
2411	(51 , happyReduce_51),
2412	(52 , happyReduce_52),
2413	(53 , happyReduce_53),
2414	(54 , happyReduce_54),
2415	(55 , happyReduce_55),
2416	(56 , happyReduce_56),
2417	(57 , happyReduce_57),
2418	(58 , happyReduce_58),
2419	(59 , happyReduce_59),
2420	(60 , happyReduce_60),
2421	(61 , happyReduce_61),
2422	(62 , happyReduce_62),
2423	(63 , happyReduce_63),
2424	(64 , happyReduce_64),
2425	(65 , happyReduce_65),
2426	(66 , happyReduce_66),
2427	(67 , happyReduce_67),
2428	(68 , happyReduce_68),
2429	(69 , happyReduce_69),
2430	(70 , happyReduce_70),
2431	(71 , happyReduce_71),
2432	(72 , happyReduce_72),
2433	(73 , happyReduce_73),
2434	(74 , happyReduce_74),
2435	(75 , happyReduce_75),
2436	(76 , happyReduce_76),
2437	(77 , happyReduce_77),
2438	(78 , happyReduce_78),
2439	(79 , happyReduce_79),
2440	(80 , happyReduce_80),
2441	(81 , happyReduce_81),
2442	(82 , happyReduce_82),
2443	(83 , happyReduce_83),
2444	(84 , happyReduce_84),
2445	(85 , happyReduce_85),
2446	(86 , happyReduce_86),
2447	(87 , happyReduce_87),
2448	(88 , happyReduce_88),
2449	(89 , happyReduce_89),
2450	(90 , happyReduce_90),
2451	(91 , happyReduce_91),
2452	(92 , happyReduce_92),
2453	(93 , happyReduce_93),
2454	(94 , happyReduce_94),
2455	(95 , happyReduce_95),
2456	(96 , happyReduce_96),
2457	(97 , happyReduce_97),
2458	(98 , happyReduce_98),
2459	(99 , happyReduce_99),
2460	(100 , happyReduce_100),
2461	(101 , happyReduce_101),
2462	(102 , happyReduce_102),
2463	(103 , happyReduce_103),
2464	(104 , happyReduce_104),
2465	(105 , happyReduce_105),
2466	(106 , happyReduce_106),
2467	(107 , happyReduce_107),
2468	(108 , happyReduce_108),
2469	(109 , happyReduce_109),
2470	(110 , happyReduce_110),
2471	(111 , happyReduce_111),
2472	(112 , happyReduce_112),
2473	(113 , happyReduce_113),
2474	(114 , happyReduce_114),
2475	(115 , happyReduce_115),
2476	(116 , happyReduce_116),
2477	(117 , happyReduce_117),
2478	(118 , happyReduce_118),
2479	(119 , happyReduce_119),
2480	(120 , happyReduce_120),
2481	(121 , happyReduce_121),
2482	(122 , happyReduce_122),
2483	(123 , happyReduce_123),
2484	(124 , happyReduce_124),
2485	(125 , happyReduce_125),
2486	(126 , happyReduce_126),
2487	(127 , happyReduce_127),
2488	(128 , happyReduce_128),
2489	(129 , happyReduce_129),
2490	(130 , happyReduce_130),
2491	(131 , happyReduce_131),
2492	(132 , happyReduce_132),
2493	(133 , happyReduce_133),
2494	(134 , happyReduce_134),
2495	(135 , happyReduce_135),
2496	(136 , happyReduce_136),
2497	(137 , happyReduce_137),
2498	(138 , happyReduce_138),
2499	(139 , happyReduce_139),
2500	(140 , happyReduce_140),
2501	(141 , happyReduce_141),
2502	(142 , happyReduce_142),
2503	(143 , happyReduce_143),
2504	(144 , happyReduce_144),
2505	(145 , happyReduce_145),
2506	(146 , happyReduce_146),
2507	(147 , happyReduce_147),
2508	(148 , happyReduce_148),
2509	(149 , happyReduce_149),
2510	(150 , happyReduce_150),
2511	(151 , happyReduce_151),
2512	(152 , happyReduce_152),
2513	(153 , happyReduce_153),
2514	(154 , happyReduce_154),
2515	(155 , happyReduce_155),
2516	(156 , happyReduce_156),
2517	(157 , happyReduce_157),
2518	(158 , happyReduce_158),
2519	(159 , happyReduce_159),
2520	(160 , happyReduce_160),
2521	(161 , happyReduce_161),
2522	(162 , happyReduce_162),
2523	(163 , happyReduce_163),
2524	(164 , happyReduce_164),
2525	(165 , happyReduce_165),
2526	(166 , happyReduce_166),
2527	(167 , happyReduce_167),
2528	(168 , happyReduce_168),
2529	(169 , happyReduce_169),
2530	(170 , happyReduce_170),
2531	(171 , happyReduce_171),
2532	(172 , happyReduce_172),
2533	(173 , happyReduce_173),
2534	(174 , happyReduce_174),
2535	(175 , happyReduce_175),
2536	(176 , happyReduce_176),
2537	(177 , happyReduce_177),
2538	(178 , happyReduce_178),
2539	(179 , happyReduce_179),
2540	(180 , happyReduce_180),
2541	(181 , happyReduce_181),
2542	(182 , happyReduce_182),
2543	(183 , happyReduce_183),
2544	(184 , happyReduce_184),
2545	(185 , happyReduce_185),
2546	(186 , happyReduce_186),
2547	(187 , happyReduce_187),
2548	(188 , happyReduce_188),
2549	(189 , happyReduce_189),
2550	(190 , happyReduce_190),
2551	(191 , happyReduce_191),
2552	(192 , happyReduce_192),
2553	(193 , happyReduce_193),
2554	(194 , happyReduce_194),
2555	(195 , happyReduce_195),
2556	(196 , happyReduce_196),
2557	(197 , happyReduce_197),
2558	(198 , happyReduce_198),
2559	(199 , happyReduce_199),
2560	(200 , happyReduce_200),
2561	(201 , happyReduce_201),
2562	(202 , happyReduce_202),
2563	(203 , happyReduce_203),
2564	(204 , happyReduce_204),
2565	(205 , happyReduce_205),
2566	(206 , happyReduce_206),
2567	(207 , happyReduce_207),
2568	(208 , happyReduce_208),
2569	(209 , happyReduce_209),
2570	(210 , happyReduce_210),
2571	(211 , happyReduce_211),
2572	(212 , happyReduce_212),
2573	(213 , happyReduce_213),
2574	(214 , happyReduce_214),
2575	(215 , happyReduce_215),
2576	(216 , happyReduce_216),
2577	(217 , happyReduce_217),
2578	(218 , happyReduce_218),
2579	(219 , happyReduce_219),
2580	(220 , happyReduce_220),
2581	(221 , happyReduce_221),
2582	(222 , happyReduce_222),
2583	(223 , happyReduce_223),
2584	(224 , happyReduce_224),
2585	(225 , happyReduce_225),
2586	(226 , happyReduce_226),
2587	(227 , happyReduce_227),
2588	(228 , happyReduce_228),
2589	(229 , happyReduce_229),
2590	(230 , happyReduce_230),
2591	(231 , happyReduce_231),
2592	(232 , happyReduce_232),
2593	(233 , happyReduce_233),
2594	(234 , happyReduce_234),
2595	(235 , happyReduce_235),
2596	(236 , happyReduce_236),
2597	(237 , happyReduce_237),
2598	(238 , happyReduce_238),
2599	(239 , happyReduce_239),
2600	(240 , happyReduce_240),
2601	(241 , happyReduce_241),
2602	(242 , happyReduce_242),
2603	(243 , happyReduce_243),
2604	(244 , happyReduce_244),
2605	(245 , happyReduce_245),
2606	(246 , happyReduce_246),
2607	(247 , happyReduce_247),
2608	(248 , happyReduce_248),
2609	(249 , happyReduce_249),
2610	(250 , happyReduce_250),
2611	(251 , happyReduce_251),
2612	(252 , happyReduce_252),
2613	(253 , happyReduce_253),
2614	(254 , happyReduce_254),
2615	(255 , happyReduce_255),
2616	(256 , happyReduce_256),
2617	(257 , happyReduce_257),
2618	(258 , happyReduce_258),
2619	(259 , happyReduce_259),
2620	(260 , happyReduce_260),
2621	(261 , happyReduce_261),
2622	(262 , happyReduce_262),
2623	(263 , happyReduce_263),
2624	(264 , happyReduce_264),
2625	(265 , happyReduce_265),
2626	(266 , happyReduce_266),
2627	(267 , happyReduce_267),
2628	(268 , happyReduce_268),
2629	(269 , happyReduce_269),
2630	(270 , happyReduce_270),
2631	(271 , happyReduce_271),
2632	(272 , happyReduce_272),
2633	(273 , happyReduce_273),
2634	(274 , happyReduce_274),
2635	(275 , happyReduce_275),
2636	(276 , happyReduce_276),
2637	(277 , happyReduce_277),
2638	(278 , happyReduce_278),
2639	(279 , happyReduce_279),
2640	(280 , happyReduce_280),
2641	(281 , happyReduce_281),
2642	(282 , happyReduce_282),
2643	(283 , happyReduce_283),
2644	(284 , happyReduce_284),
2645	(285 , happyReduce_285),
2646	(286 , happyReduce_286),
2647	(287 , happyReduce_287),
2648	(288 , happyReduce_288),
2649	(289 , happyReduce_289),
2650	(290 , happyReduce_290),
2651	(291 , happyReduce_291),
2652	(292 , happyReduce_292),
2653	(293 , happyReduce_293),
2654	(294 , happyReduce_294),
2655	(295 , happyReduce_295),
2656	(296 , happyReduce_296),
2657	(297 , happyReduce_297),
2658	(298 , happyReduce_298),
2659	(299 , happyReduce_299),
2660	(300 , happyReduce_300),
2661	(301 , happyReduce_301),
2662	(302 , happyReduce_302),
2663	(303 , happyReduce_303),
2664	(304 , happyReduce_304),
2665	(305 , happyReduce_305),
2666	(306 , happyReduce_306),
2667	(307 , happyReduce_307),
2668	(308 , happyReduce_308),
2669	(309 , happyReduce_309),
2670	(310 , happyReduce_310),
2671	(311 , happyReduce_311),
2672	(312 , happyReduce_312),
2673	(313 , happyReduce_313),
2674	(314 , happyReduce_314),
2675	(315 , happyReduce_315),
2676	(316 , happyReduce_316),
2677	(317 , happyReduce_317),
2678	(318 , happyReduce_318),
2679	(319 , happyReduce_319),
2680	(320 , happyReduce_320),
2681	(321 , happyReduce_321),
2682	(322 , happyReduce_322),
2683	(323 , happyReduce_323),
2684	(324 , happyReduce_324),
2685	(325 , happyReduce_325),
2686	(326 , happyReduce_326),
2687	(327 , happyReduce_327),
2688	(328 , happyReduce_328),
2689	(329 , happyReduce_329),
2690	(330 , happyReduce_330),
2691	(331 , happyReduce_331),
2692	(332 , happyReduce_332),
2693	(333 , happyReduce_333),
2694	(334 , happyReduce_334),
2695	(335 , happyReduce_335),
2696	(336 , happyReduce_336),
2697	(337 , happyReduce_337),
2698	(338 , happyReduce_338),
2699	(339 , happyReduce_339),
2700	(340 , happyReduce_340),
2701	(341 , happyReduce_341),
2702	(342 , happyReduce_342),
2703	(343 , happyReduce_343),
2704	(344 , happyReduce_344),
2705	(345 , happyReduce_345),
2706	(346 , happyReduce_346),
2707	(347 , happyReduce_347),
2708	(348 , happyReduce_348),
2709	(349 , happyReduce_349),
2710	(350 , happyReduce_350),
2711	(351 , happyReduce_351),
2712	(352 , happyReduce_352),
2713	(353 , happyReduce_353),
2714	(354 , happyReduce_354),
2715	(355 , happyReduce_355),
2716	(356 , happyReduce_356),
2717	(357 , happyReduce_357),
2718	(358 , happyReduce_358),
2719	(359 , happyReduce_359),
2720	(360 , happyReduce_360),
2721	(361 , happyReduce_361),
2722	(362 , happyReduce_362),
2723	(363 , happyReduce_363),
2724	(364 , happyReduce_364),
2725	(365 , happyReduce_365),
2726	(366 , happyReduce_366),
2727	(367 , happyReduce_367),
2728	(368 , happyReduce_368),
2729	(369 , happyReduce_369),
2730	(370 , happyReduce_370),
2731	(371 , happyReduce_371),
2732	(372 , happyReduce_372),
2733	(373 , happyReduce_373),
2734	(374 , happyReduce_374),
2735	(375 , happyReduce_375),
2736	(376 , happyReduce_376),
2737	(377 , happyReduce_377),
2738	(378 , happyReduce_378),
2739	(379 , happyReduce_379),
2740	(380 , happyReduce_380),
2741	(381 , happyReduce_381),
2742	(382 , happyReduce_382),
2743	(383 , happyReduce_383),
2744	(384 , happyReduce_384),
2745	(385 , happyReduce_385),
2746	(386 , happyReduce_386),
2747	(387 , happyReduce_387),
2748	(388 , happyReduce_388),
2749	(389 , happyReduce_389),
2750	(390 , happyReduce_390),
2751	(391 , happyReduce_391),
2752	(392 , happyReduce_392),
2753	(393 , happyReduce_393),
2754	(394 , happyReduce_394),
2755	(395 , happyReduce_395),
2756	(396 , happyReduce_396),
2757	(397 , happyReduce_397),
2758	(398 , happyReduce_398),
2759	(399 , happyReduce_399),
2760	(400 , happyReduce_400),
2761	(401 , happyReduce_401),
2762	(402 , happyReduce_402),
2763	(403 , happyReduce_403),
2764	(404 , happyReduce_404),
2765	(405 , happyReduce_405),
2766	(406 , happyReduce_406),
2767	(407 , happyReduce_407),
2768	(408 , happyReduce_408),
2769	(409 , happyReduce_409),
2770	(410 , happyReduce_410),
2771	(411 , happyReduce_411),
2772	(412 , happyReduce_412),
2773	(413 , happyReduce_413),
2774	(414 , happyReduce_414),
2775	(415 , happyReduce_415),
2776	(416 , happyReduce_416),
2777	(417 , happyReduce_417),
2778	(418 , happyReduce_418),
2779	(419 , happyReduce_419),
2780	(420 , happyReduce_420),
2781	(421 , happyReduce_421),
2782	(422 , happyReduce_422),
2783	(423 , happyReduce_423),
2784	(424 , happyReduce_424),
2785	(425 , happyReduce_425),
2786	(426 , happyReduce_426),
2787	(427 , happyReduce_427),
2788	(428 , happyReduce_428),
2789	(429 , happyReduce_429),
2790	(430 , happyReduce_430),
2791	(431 , happyReduce_431),
2792	(432 , happyReduce_432),
2793	(433 , happyReduce_433),
2794	(434 , happyReduce_434),
2795	(435 , happyReduce_435),
2796	(436 , happyReduce_436),
2797	(437 , happyReduce_437),
2798	(438 , happyReduce_438),
2799	(439 , happyReduce_439),
2800	(440 , happyReduce_440),
2801	(441 , happyReduce_441),
2802	(442 , happyReduce_442),
2803	(443 , happyReduce_443),
2804	(444 , happyReduce_444),
2805	(445 , happyReduce_445),
2806	(446 , happyReduce_446),
2807	(447 , happyReduce_447),
2808	(448 , happyReduce_448),
2809	(449 , happyReduce_449),
2810	(450 , happyReduce_450),
2811	(451 , happyReduce_451),
2812	(452 , happyReduce_452),
2813	(453 , happyReduce_453),
2814	(454 , happyReduce_454),
2815	(455 , happyReduce_455),
2816	(456 , happyReduce_456),
2817	(457 , happyReduce_457),
2818	(458 , happyReduce_458),
2819	(459 , happyReduce_459),
2820	(460 , happyReduce_460),
2821	(461 , happyReduce_461),
2822	(462 , happyReduce_462),
2823	(463 , happyReduce_463),
2824	(464 , happyReduce_464),
2825	(465 , happyReduce_465),
2826	(466 , happyReduce_466),
2827	(467 , happyReduce_467),
2828	(468 , happyReduce_468),
2829	(469 , happyReduce_469),
2830	(470 , happyReduce_470),
2831	(471 , happyReduce_471),
2832	(472 , happyReduce_472),
2833	(473 , happyReduce_473),
2834	(474 , happyReduce_474),
2835	(475 , happyReduce_475),
2836	(476 , happyReduce_476),
2837	(477 , happyReduce_477),
2838	(478 , happyReduce_478),
2839	(479 , happyReduce_479),
2840	(480 , happyReduce_480),
2841	(481 , happyReduce_481),
2842	(482 , happyReduce_482),
2843	(483 , happyReduce_483),
2844	(484 , happyReduce_484),
2845	(485 , happyReduce_485),
2846	(486 , happyReduce_486),
2847	(487 , happyReduce_487),
2848	(488 , happyReduce_488),
2849	(489 , happyReduce_489),
2850	(490 , happyReduce_490),
2851	(491 , happyReduce_491),
2852	(492 , happyReduce_492),
2853	(493 , happyReduce_493),
2854	(494 , happyReduce_494),
2855	(495 , happyReduce_495),
2856	(496 , happyReduce_496),
2857	(497 , happyReduce_497),
2858	(498 , happyReduce_498),
2859	(499 , happyReduce_499),
2860	(500 , happyReduce_500),
2861	(501 , happyReduce_501),
2862	(502 , happyReduce_502),
2863	(503 , happyReduce_503),
2864	(504 , happyReduce_504),
2865	(505 , happyReduce_505),
2866	(506 , happyReduce_506),
2867	(507 , happyReduce_507),
2868	(508 , happyReduce_508),
2869	(509 , happyReduce_509),
2870	(510 , happyReduce_510),
2871	(511 , happyReduce_511),
2872	(512 , happyReduce_512),
2873	(513 , happyReduce_513),
2874	(514 , happyReduce_514),
2875	(515 , happyReduce_515),
2876	(516 , happyReduce_516),
2877	(517 , happyReduce_517),
2878	(518 , happyReduce_518),
2879	(519 , happyReduce_519),
2880	(520 , happyReduce_520),
2881	(521 , happyReduce_521),
2882	(522 , happyReduce_522),
2883	(523 , happyReduce_523),
2884	(524 , happyReduce_524),
2885	(525 , happyReduce_525),
2886	(526 , happyReduce_526),
2887	(527 , happyReduce_527),
2888	(528 , happyReduce_528),
2889	(529 , happyReduce_529),
2890	(530 , happyReduce_530),
2891	(531 , happyReduce_531),
2892	(532 , happyReduce_532),
2893	(533 , happyReduce_533),
2894	(534 , happyReduce_534),
2895	(535 , happyReduce_535),
2896	(536 , happyReduce_536),
2897	(537 , happyReduce_537),
2898	(538 , happyReduce_538),
2899	(539 , happyReduce_539),
2900	(540 , happyReduce_540),
2901	(541 , happyReduce_541),
2902	(542 , happyReduce_542),
2903	(543 , happyReduce_543),
2904	(544 , happyReduce_544),
2905	(545 , happyReduce_545),
2906	(546 , happyReduce_546),
2907	(547 , happyReduce_547),
2908	(548 , happyReduce_548),
2909	(549 , happyReduce_549),
2910	(550 , happyReduce_550),
2911	(551 , happyReduce_551),
2912	(552 , happyReduce_552),
2913	(553 , happyReduce_553),
2914	(554 , happyReduce_554),
2915	(555 , happyReduce_555),
2916	(556 , happyReduce_556),
2917	(557 , happyReduce_557),
2918	(558 , happyReduce_558),
2919	(559 , happyReduce_559),
2920	(560 , happyReduce_560),
2921	(561 , happyReduce_561),
2922	(562 , happyReduce_562),
2923	(563 , happyReduce_563),
2924	(564 , happyReduce_564),
2925	(565 , happyReduce_565),
2926	(566 , happyReduce_566),
2927	(567 , happyReduce_567),
2928	(568 , happyReduce_568),
2929	(569 , happyReduce_569),
2930	(570 , happyReduce_570),
2931	(571 , happyReduce_571),
2932	(572 , happyReduce_572),
2933	(573 , happyReduce_573),
2934	(574 , happyReduce_574),
2935	(575 , happyReduce_575),
2936	(576 , happyReduce_576),
2937	(577 , happyReduce_577),
2938	(578 , happyReduce_578),
2939	(579 , happyReduce_579),
2940	(580 , happyReduce_580),
2941	(581 , happyReduce_581),
2942	(582 , happyReduce_582),
2943	(583 , happyReduce_583),
2944	(584 , happyReduce_584),
2945	(585 , happyReduce_585),
2946	(586 , happyReduce_586),
2947	(587 , happyReduce_587),
2948	(588 , happyReduce_588),
2949	(589 , happyReduce_589),
2950	(590 , happyReduce_590),
2951	(591 , happyReduce_591),
2952	(592 , happyReduce_592),
2953	(593 , happyReduce_593),
2954	(594 , happyReduce_594),
2955	(595 , happyReduce_595),
2956	(596 , happyReduce_596),
2957	(597 , happyReduce_597),
2958	(598 , happyReduce_598),
2959	(599 , happyReduce_599),
2960	(600 , happyReduce_600),
2961	(601 , happyReduce_601),
2962	(602 , happyReduce_602),
2963	(603 , happyReduce_603),
2964	(604 , happyReduce_604),
2965	(605 , happyReduce_605),
2966	(606 , happyReduce_606),
2967	(607 , happyReduce_607),
2968	(608 , happyReduce_608),
2969	(609 , happyReduce_609),
2970	(610 , happyReduce_610),
2971	(611 , happyReduce_611),
2972	(612 , happyReduce_612),
2973	(613 , happyReduce_613),
2974	(614 , happyReduce_614),
2975	(615 , happyReduce_615),
2976	(616 , happyReduce_616),
2977	(617 , happyReduce_617),
2978	(618 , happyReduce_618),
2979	(619 , happyReduce_619),
2980	(620 , happyReduce_620),
2981	(621 , happyReduce_621),
2982	(622 , happyReduce_622),
2983	(623 , happyReduce_623),
2984	(624 , happyReduce_624),
2985	(625 , happyReduce_625),
2986	(626 , happyReduce_626),
2987	(627 , happyReduce_627),
2988	(628 , happyReduce_628),
2989	(629 , happyReduce_629),
2990	(630 , happyReduce_630),
2991	(631 , happyReduce_631),
2992	(632 , happyReduce_632),
2993	(633 , happyReduce_633),
2994	(634 , happyReduce_634),
2995	(635 , happyReduce_635),
2996	(636 , happyReduce_636),
2997	(637 , happyReduce_637),
2998	(638 , happyReduce_638),
2999	(639 , happyReduce_639),
3000	(640 , happyReduce_640),
3001	(641 , happyReduce_641),
3002	(642 , happyReduce_642),
3003	(643 , happyReduce_643),
3004	(644 , happyReduce_644),
3005	(645 , happyReduce_645),
3006	(646 , happyReduce_646),
3007	(647 , happyReduce_647),
3008	(648 , happyReduce_648),
3009	(649 , happyReduce_649),
3010	(650 , happyReduce_650),
3011	(651 , happyReduce_651),
3012	(652 , happyReduce_652),
3013	(653 , happyReduce_653),
3014	(654 , happyReduce_654),
3015	(655 , happyReduce_655),
3016	(656 , happyReduce_656),
3017	(657 , happyReduce_657),
3018	(658 , happyReduce_658),
3019	(659 , happyReduce_659),
3020	(660 , happyReduce_660),
3021	(661 , happyReduce_661),
3022	(662 , happyReduce_662),
3023	(663 , happyReduce_663),
3024	(664 , happyReduce_664),
3025	(665 , happyReduce_665),
3026	(666 , happyReduce_666),
3027	(667 , happyReduce_667),
3028	(668 , happyReduce_668),
3029	(669 , happyReduce_669),
3030	(670 , happyReduce_670),
3031	(671 , happyReduce_671),
3032	(672 , happyReduce_672),
3033	(673 , happyReduce_673),
3034	(674 , happyReduce_674),
3035	(675 , happyReduce_675),
3036	(676 , happyReduce_676),
3037	(677 , happyReduce_677),
3038	(678 , happyReduce_678),
3039	(679 , happyReduce_679),
3040	(680 , happyReduce_680),
3041	(681 , happyReduce_681),
3042	(682 , happyReduce_682),
3043	(683 , happyReduce_683),
3044	(684 , happyReduce_684),
3045	(685 , happyReduce_685),
3046	(686 , happyReduce_686),
3047	(687 , happyReduce_687),
3048	(688 , happyReduce_688),
3049	(689 , happyReduce_689),
3050	(690 , happyReduce_690),
3051	(691 , happyReduce_691),
3052	(692 , happyReduce_692),
3053	(693 , happyReduce_693),
3054	(694 , happyReduce_694),
3055	(695 , happyReduce_695),
3056	(696 , happyReduce_696),
3057	(697 , happyReduce_697),
3058	(698 , happyReduce_698),
3059	(699 , happyReduce_699),
3060	(700 , happyReduce_700),
3061	(701 , happyReduce_701),
3062	(702 , happyReduce_702),
3063	(703 , happyReduce_703),
3064	(704 , happyReduce_704),
3065	(705 , happyReduce_705),
3066	(706 , happyReduce_706),
3067	(707 , happyReduce_707),
3068	(708 , happyReduce_708),
3069	(709 , happyReduce_709),
3070	(710 , happyReduce_710),
3071	(711 , happyReduce_711),
3072	(712 , happyReduce_712),
3073	(713 , happyReduce_713),
3074	(714 , happyReduce_714),
3075	(715 , happyReduce_715),
3076	(716 , happyReduce_716),
3077	(717 , happyReduce_717),
3078	(718 , happyReduce_718),
3079	(719 , happyReduce_719),
3080	(720 , happyReduce_720),
3081	(721 , happyReduce_721),
3082	(722 , happyReduce_722),
3083	(723 , happyReduce_723),
3084	(724 , happyReduce_724),
3085	(725 , happyReduce_725),
3086	(726 , happyReduce_726),
3087	(727 , happyReduce_727),
3088	(728 , happyReduce_728),
3089	(729 , happyReduce_729),
3090	(730 , happyReduce_730),
3091	(731 , happyReduce_731),
3092	(732 , happyReduce_732),
3093	(733 , happyReduce_733),
3094	(734 , happyReduce_734),
3095	(735 , happyReduce_735),
3096	(736 , happyReduce_736),
3097	(737 , happyReduce_737),
3098	(738 , happyReduce_738),
3099	(739 , happyReduce_739),
3100	(740 , happyReduce_740),
3101	(741 , happyReduce_741),
3102	(742 , happyReduce_742),
3103	(743 , happyReduce_743),
3104	(744 , happyReduce_744),
3105	(745 , happyReduce_745),
3106	(746 , happyReduce_746),
3107	(747 , happyReduce_747),
3108	(748 , happyReduce_748),
3109	(749 , happyReduce_749),
3110	(750 , happyReduce_750),
3111	(751 , happyReduce_751),
3112	(752 , happyReduce_752),
3113	(753 , happyReduce_753),
3114	(754 , happyReduce_754),
3115	(755 , happyReduce_755),
3116	(756 , happyReduce_756),
3117	(757 , happyReduce_757),
3118	(758 , happyReduce_758),
3119	(759 , happyReduce_759),
3120	(760 , happyReduce_760),
3121	(761 , happyReduce_761),
3122	(762 , happyReduce_762),
3123	(763 , happyReduce_763),
3124	(764 , happyReduce_764),
3125	(765 , happyReduce_765),
3126	(766 , happyReduce_766),
3127	(767 , happyReduce_767),
3128	(768 , happyReduce_768),
3129	(769 , happyReduce_769),
3130	(770 , happyReduce_770),
3131	(771 , happyReduce_771),
3132	(772 , happyReduce_772),
3133	(773 , happyReduce_773),
3134	(774 , happyReduce_774),
3135	(775 , happyReduce_775),
3136	(776 , happyReduce_776),
3137	(777 , happyReduce_777),
3138	(778 , happyReduce_778),
3139	(779 , happyReduce_779),
3140	(780 , happyReduce_780),
3141	(781 , happyReduce_781),
3142	(782 , happyReduce_782),
3143	(783 , happyReduce_783),
3144	(784 , happyReduce_784),
3145	(785 , happyReduce_785),
3146	(786 , happyReduce_786),
3147	(787 , happyReduce_787),
3148	(788 , happyReduce_788),
3149	(789 , happyReduce_789),
3150	(790 , happyReduce_790),
3151	(791 , happyReduce_791),
3152	(792 , happyReduce_792),
3153	(793 , happyReduce_793),
3154	(794 , happyReduce_794),
3155	(795 , happyReduce_795),
3156	(796 , happyReduce_796),
3157	(797 , happyReduce_797),
3158	(798 , happyReduce_798),
3159	(799 , happyReduce_799),
3160	(800 , happyReduce_800),
3161	(801 , happyReduce_801),
3162	(802 , happyReduce_802),
3163	(803 , happyReduce_803),
3164	(804 , happyReduce_804),
3165	(805 , happyReduce_805),
3166	(806 , happyReduce_806),
3167	(807 , happyReduce_807),
3168	(808 , happyReduce_808),
3169	(809 , happyReduce_809),
3170	(810 , happyReduce_810),
3171	(811 , happyReduce_811),
3172	(812 , happyReduce_812),
3173	(813 , happyReduce_813),
3174	(814 , happyReduce_814),
3175	(815 , happyReduce_815),
3176	(816 , happyReduce_816),
3177	(817 , happyReduce_817),
3178	(818 , happyReduce_818),
3179	(819 , happyReduce_819),
3180	(820 , happyReduce_820),
3181	(821 , happyReduce_821),
3182	(822 , happyReduce_822),
3183	(823 , happyReduce_823),
3184	(824 , happyReduce_824),
3185	(825 , happyReduce_825),
3186	(826 , happyReduce_826),
3187	(827 , happyReduce_827),
3188	(828 , happyReduce_828),
3189	(829 , happyReduce_829),
3190	(830 , happyReduce_830),
3191	(831 , happyReduce_831),
3192	(832 , happyReduce_832),
3193	(833 , happyReduce_833),
3194	(834 , happyReduce_834)
3195	]
3196
3197happy_n_terms = 154 :: Int
3198happy_n_nonterms = 314 :: Int
3199
3200happyReduce_13 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3201happyReduce_13 = happySpecReduce_1  0# happyReduction_13
3202happyReduction_13 happy_x_1
3203	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
3204	happyIn16
3205		 (happy_var_1
3206	)}
3207
3208happyReduce_14 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3209happyReduce_14 = happySpecReduce_1  0# happyReduction_14
3210happyReduction_14 happy_x_1
3211	 =  case happyOut274 happy_x_1 of { (HappyWrap274 happy_var_1) ->
3212	happyIn16
3213		 (happy_var_1
3214	)}
3215
3216happyReduce_15 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3217happyReduce_15 = happySpecReduce_1  0# happyReduction_15
3218happyReduction_15 happy_x_1
3219	 =  case happyOut297 happy_x_1 of { (HappyWrap297 happy_var_1) ->
3220	happyIn16
3221		 (happy_var_1
3222	)}
3223
3224happyReduce_16 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3225happyReduce_16 = happySpecReduce_1  0# happyReduction_16
3226happyReduction_16 happy_x_1
3227	 =  case happyOut281 happy_x_1 of { (HappyWrap281 happy_var_1) ->
3228	happyIn16
3229		 (happy_var_1
3230	)}
3231
3232happyReduce_17 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3233happyReduce_17 = happyMonadReduce 3# 0# happyReduction_17
3234happyReduction_17 (happy_x_3 `HappyStk`
3235	happy_x_2 `HappyStk`
3236	happy_x_1 `HappyStk`
3237	happyRest) tk
3238	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
3239	case happyOutTok happy_x_2 of { happy_var_2 ->
3240	case happyOutTok happy_x_3 of { happy_var_3 ->
3241	( ams (sLL happy_var_1 happy_var_3 $ getRdrName funTyCon)
3242                               [mop happy_var_1,mu AnnRarrow happy_var_2,mcp happy_var_3])}}})
3243	) (\r -> happyReturn (happyIn16 r))
3244
3245happyReduce_18 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3246happyReduce_18 = happyMonadReduce 1# 0# happyReduction_18
3247happyReduction_18 (happy_x_1 `HappyStk`
3248	happyRest) tk
3249	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
3250	( ams (sLL happy_var_1 happy_var_1 $ getRdrName funTyCon)
3251                               [mu AnnRarrow happy_var_1])})
3252	) (\r -> happyReturn (happyIn16 r))
3253
3254happyReduce_19 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3255happyReduce_19 = happyMonadReduce 3# 0# happyReduction_19
3256happyReduction_19 (happy_x_3 `HappyStk`
3257	happy_x_2 `HappyStk`
3258	happy_x_1 `HappyStk`
3259	happyRest) tk
3260	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
3261	case happyOutTok happy_x_2 of { happy_var_2 ->
3262	case happyOutTok happy_x_3 of { happy_var_3 ->
3263	( ams (sLL happy_var_1 happy_var_3 $ eqTyCon_RDR)
3264                               [mop happy_var_1,mj AnnTilde happy_var_2,mcp happy_var_3])}}})
3265	) (\r -> happyReturn (happyIn16 r))
3266
3267happyReduce_20 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3268happyReduce_20 = happySpecReduce_3  1# happyReduction_20
3269happyReduction_20 happy_x_3
3270	happy_x_2
3271	happy_x_1
3272	 =  case happyOut18 happy_x_2 of { (HappyWrap18 happy_var_2) ->
3273	happyIn17
3274		 (fromOL happy_var_2
3275	)}
3276
3277happyReduce_21 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3278happyReduce_21 = happySpecReduce_3  1# happyReduction_21
3279happyReduction_21 happy_x_3
3280	happy_x_2
3281	happy_x_1
3282	 =  case happyOut18 happy_x_2 of { (HappyWrap18 happy_var_2) ->
3283	happyIn17
3284		 (fromOL happy_var_2
3285	)}
3286
3287happyReduce_22 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3288happyReduce_22 = happySpecReduce_3  2# happyReduction_22
3289happyReduction_22 happy_x_3
3290	happy_x_2
3291	happy_x_1
3292	 =  case happyOut18 happy_x_1 of { (HappyWrap18 happy_var_1) ->
3293	case happyOut19 happy_x_3 of { (HappyWrap19 happy_var_3) ->
3294	happyIn18
3295		 (happy_var_1 `appOL` unitOL happy_var_3
3296	)}}
3297
3298happyReduce_23 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3299happyReduce_23 = happySpecReduce_2  2# happyReduction_23
3300happyReduction_23 happy_x_2
3301	happy_x_1
3302	 =  case happyOut18 happy_x_1 of { (HappyWrap18 happy_var_1) ->
3303	happyIn18
3304		 (happy_var_1
3305	)}
3306
3307happyReduce_24 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3308happyReduce_24 = happySpecReduce_1  2# happyReduction_24
3309happyReduction_24 happy_x_1
3310	 =  case happyOut19 happy_x_1 of { (HappyWrap19 happy_var_1) ->
3311	happyIn18
3312		 (unitOL happy_var_1
3313	)}
3314
3315happyReduce_25 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3316happyReduce_25 = happyReduce 4# 3# happyReduction_25
3317happyReduction_25 (happy_x_4 `HappyStk`
3318	happy_x_3 `HappyStk`
3319	happy_x_2 `HappyStk`
3320	happy_x_1 `HappyStk`
3321	happyRest)
3322	 = case happyOutTok happy_x_1 of { happy_var_1 ->
3323	case happyOut24 happy_x_2 of { (HappyWrap24 happy_var_2) ->
3324	case happyOut30 happy_x_4 of { (HappyWrap30 happy_var_4) ->
3325	happyIn19
3326		 (sL1 happy_var_1 $ HsUnit { hsunitName = happy_var_2
3327                              , hsunitBody = fromOL happy_var_4 }
3328	) `HappyStk` happyRest}}}
3329
3330happyReduce_26 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3331happyReduce_26 = happySpecReduce_1  4# happyReduction_26
3332happyReduction_26 happy_x_1
3333	 =  case happyOut24 happy_x_1 of { (HappyWrap24 happy_var_1) ->
3334	happyIn20
3335		 (sL1 happy_var_1 $ HsUnitId happy_var_1 []
3336	)}
3337
3338happyReduce_27 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3339happyReduce_27 = happyReduce 4# 4# happyReduction_27
3340happyReduction_27 (happy_x_4 `HappyStk`
3341	happy_x_3 `HappyStk`
3342	happy_x_2 `HappyStk`
3343	happy_x_1 `HappyStk`
3344	happyRest)
3345	 = case happyOut24 happy_x_1 of { (HappyWrap24 happy_var_1) ->
3346	case happyOut21 happy_x_3 of { (HappyWrap21 happy_var_3) ->
3347	case happyOutTok happy_x_4 of { happy_var_4 ->
3348	happyIn20
3349		 (sLL happy_var_1 happy_var_4 $ HsUnitId happy_var_1 (fromOL happy_var_3)
3350	) `HappyStk` happyRest}}}
3351
3352happyReduce_28 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3353happyReduce_28 = happySpecReduce_3  5# happyReduction_28
3354happyReduction_28 happy_x_3
3355	happy_x_2
3356	happy_x_1
3357	 =  case happyOut21 happy_x_1 of { (HappyWrap21 happy_var_1) ->
3358	case happyOut22 happy_x_3 of { (HappyWrap22 happy_var_3) ->
3359	happyIn21
3360		 (happy_var_1 `appOL` unitOL happy_var_3
3361	)}}
3362
3363happyReduce_29 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3364happyReduce_29 = happySpecReduce_2  5# happyReduction_29
3365happyReduction_29 happy_x_2
3366	happy_x_1
3367	 =  case happyOut21 happy_x_1 of { (HappyWrap21 happy_var_1) ->
3368	happyIn21
3369		 (happy_var_1
3370	)}
3371
3372happyReduce_30 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3373happyReduce_30 = happySpecReduce_1  5# happyReduction_30
3374happyReduction_30 happy_x_1
3375	 =  case happyOut22 happy_x_1 of { (HappyWrap22 happy_var_1) ->
3376	happyIn21
3377		 (unitOL happy_var_1
3378	)}
3379
3380happyReduce_31 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3381happyReduce_31 = happySpecReduce_3  6# happyReduction_31
3382happyReduction_31 happy_x_3
3383	happy_x_2
3384	happy_x_1
3385	 =  case happyOut319 happy_x_1 of { (HappyWrap319 happy_var_1) ->
3386	case happyOut23 happy_x_3 of { (HappyWrap23 happy_var_3) ->
3387	happyIn22
3388		 (sLL happy_var_1 happy_var_3 $ (happy_var_1, happy_var_3)
3389	)}}
3390
3391happyReduce_32 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3392happyReduce_32 = happyReduce 4# 6# happyReduction_32
3393happyReduction_32 (happy_x_4 `HappyStk`
3394	happy_x_3 `HappyStk`
3395	happy_x_2 `HappyStk`
3396	happy_x_1 `HappyStk`
3397	happyRest)
3398	 = case happyOut319 happy_x_1 of { (HappyWrap319 happy_var_1) ->
3399	case happyOutTok happy_x_2 of { happy_var_2 ->
3400	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3401	case happyOutTok happy_x_4 of { happy_var_4 ->
3402	happyIn22
3403		 (sLL happy_var_1 happy_var_4 $ (happy_var_1, sLL happy_var_2 happy_var_4 $ HsModuleVar happy_var_3)
3404	) `HappyStk` happyRest}}}}
3405
3406happyReduce_33 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3407happyReduce_33 = happySpecReduce_3  7# happyReduction_33
3408happyReduction_33 happy_x_3
3409	happy_x_2
3410	happy_x_1
3411	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3412	case happyOut319 happy_x_2 of { (HappyWrap319 happy_var_2) ->
3413	case happyOutTok happy_x_3 of { happy_var_3 ->
3414	happyIn23
3415		 (sLL happy_var_1 happy_var_3 $ HsModuleVar happy_var_2
3416	)}}}
3417
3418happyReduce_34 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3419happyReduce_34 = happySpecReduce_3  7# happyReduction_34
3420happyReduction_34 happy_x_3
3421	happy_x_2
3422	happy_x_1
3423	 =  case happyOut20 happy_x_1 of { (HappyWrap20 happy_var_1) ->
3424	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3425	happyIn23
3426		 (sLL happy_var_1 happy_var_3 $ HsModuleId happy_var_1 happy_var_3
3427	)}}
3428
3429happyReduce_35 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3430happyReduce_35 = happySpecReduce_1  8# happyReduction_35
3431happyReduction_35 happy_x_1
3432	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3433	happyIn24
3434		 (sL1 happy_var_1 $ PackageName (getSTRING happy_var_1)
3435	)}
3436
3437happyReduce_36 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3438happyReduce_36 = happySpecReduce_1  8# happyReduction_36
3439happyReduction_36 happy_x_1
3440	 =  case happyOut26 happy_x_1 of { (HappyWrap26 happy_var_1) ->
3441	happyIn24
3442		 (sL1 happy_var_1 $ PackageName (unLoc happy_var_1)
3443	)}
3444
3445happyReduce_37 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3446happyReduce_37 = happySpecReduce_1  9# happyReduction_37
3447happyReduction_37 happy_x_1
3448	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3449	happyIn25
3450		 (sL1 happy_var_1 $ getVARID happy_var_1
3451	)}
3452
3453happyReduce_38 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3454happyReduce_38 = happySpecReduce_1  9# happyReduction_38
3455happyReduction_38 happy_x_1
3456	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3457	happyIn25
3458		 (sL1 happy_var_1 $ getCONID happy_var_1
3459	)}
3460
3461happyReduce_39 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3462happyReduce_39 = happySpecReduce_1  9# happyReduction_39
3463happyReduction_39 happy_x_1
3464	 =  case happyOut311 happy_x_1 of { (HappyWrap311 happy_var_1) ->
3465	happyIn25
3466		 (happy_var_1
3467	)}
3468
3469happyReduce_40 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3470happyReduce_40 = happySpecReduce_1  10# happyReduction_40
3471happyReduction_40 happy_x_1
3472	 =  case happyOut25 happy_x_1 of { (HappyWrap25 happy_var_1) ->
3473	happyIn26
3474		 (happy_var_1
3475	)}
3476
3477happyReduce_41 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3478happyReduce_41 = happySpecReduce_3  10# happyReduction_41
3479happyReduction_41 happy_x_3
3480	happy_x_2
3481	happy_x_1
3482	 =  case happyOut25 happy_x_1 of { (HappyWrap25 happy_var_1) ->
3483	case happyOut26 happy_x_3 of { (HappyWrap26 happy_var_3) ->
3484	happyIn26
3485		 (sLL happy_var_1 happy_var_3 $ appendFS (unLoc happy_var_1) (consFS '-' (unLoc happy_var_3))
3486	)}}
3487
3488happyReduce_42 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3489happyReduce_42 = happySpecReduce_0  11# happyReduction_42
3490happyReduction_42  =  happyIn27
3491		 (Nothing
3492	)
3493
3494happyReduce_43 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3495happyReduce_43 = happySpecReduce_3  11# happyReduction_43
3496happyReduction_43 happy_x_3
3497	happy_x_2
3498	happy_x_1
3499	 =  case happyOut28 happy_x_2 of { (HappyWrap28 happy_var_2) ->
3500	happyIn27
3501		 (Just (fromOL happy_var_2)
3502	)}
3503
3504happyReduce_44 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3505happyReduce_44 = happySpecReduce_3  12# happyReduction_44
3506happyReduction_44 happy_x_3
3507	happy_x_2
3508	happy_x_1
3509	 =  case happyOut28 happy_x_1 of { (HappyWrap28 happy_var_1) ->
3510	case happyOut29 happy_x_3 of { (HappyWrap29 happy_var_3) ->
3511	happyIn28
3512		 (happy_var_1 `appOL` unitOL happy_var_3
3513	)}}
3514
3515happyReduce_45 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3516happyReduce_45 = happySpecReduce_2  12# happyReduction_45
3517happyReduction_45 happy_x_2
3518	happy_x_1
3519	 =  case happyOut28 happy_x_1 of { (HappyWrap28 happy_var_1) ->
3520	happyIn28
3521		 (happy_var_1
3522	)}
3523
3524happyReduce_46 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3525happyReduce_46 = happySpecReduce_1  12# happyReduction_46
3526happyReduction_46 happy_x_1
3527	 =  case happyOut29 happy_x_1 of { (HappyWrap29 happy_var_1) ->
3528	happyIn28
3529		 (unitOL happy_var_1
3530	)}
3531
3532happyReduce_47 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3533happyReduce_47 = happySpecReduce_3  13# happyReduction_47
3534happyReduction_47 happy_x_3
3535	happy_x_2
3536	happy_x_1
3537	 =  case happyOut319 happy_x_1 of { (HappyWrap319 happy_var_1) ->
3538	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3539	happyIn29
3540		 (sLL happy_var_1 happy_var_3 $ Renaming happy_var_1 (Just happy_var_3)
3541	)}}
3542
3543happyReduce_48 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3544happyReduce_48 = happySpecReduce_1  13# happyReduction_48
3545happyReduction_48 happy_x_1
3546	 =  case happyOut319 happy_x_1 of { (HappyWrap319 happy_var_1) ->
3547	happyIn29
3548		 (sL1 happy_var_1    $ Renaming happy_var_1 Nothing
3549	)}
3550
3551happyReduce_49 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3552happyReduce_49 = happySpecReduce_3  14# happyReduction_49
3553happyReduction_49 happy_x_3
3554	happy_x_2
3555	happy_x_1
3556	 =  case happyOut31 happy_x_2 of { (HappyWrap31 happy_var_2) ->
3557	happyIn30
3558		 (happy_var_2
3559	)}
3560
3561happyReduce_50 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3562happyReduce_50 = happySpecReduce_3  14# happyReduction_50
3563happyReduction_50 happy_x_3
3564	happy_x_2
3565	happy_x_1
3566	 =  case happyOut31 happy_x_2 of { (HappyWrap31 happy_var_2) ->
3567	happyIn30
3568		 (happy_var_2
3569	)}
3570
3571happyReduce_51 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3572happyReduce_51 = happySpecReduce_3  15# happyReduction_51
3573happyReduction_51 happy_x_3
3574	happy_x_2
3575	happy_x_1
3576	 =  case happyOut31 happy_x_1 of { (HappyWrap31 happy_var_1) ->
3577	case happyOut32 happy_x_3 of { (HappyWrap32 happy_var_3) ->
3578	happyIn31
3579		 (happy_var_1 `appOL` unitOL happy_var_3
3580	)}}
3581
3582happyReduce_52 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3583happyReduce_52 = happySpecReduce_2  15# happyReduction_52
3584happyReduction_52 happy_x_2
3585	happy_x_1
3586	 =  case happyOut31 happy_x_1 of { (HappyWrap31 happy_var_1) ->
3587	happyIn31
3588		 (happy_var_1
3589	)}
3590
3591happyReduce_53 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3592happyReduce_53 = happySpecReduce_1  15# happyReduction_53
3593happyReduction_53 happy_x_1
3594	 =  case happyOut32 happy_x_1 of { (HappyWrap32 happy_var_1) ->
3595	happyIn31
3596		 (unitOL happy_var_1
3597	)}
3598
3599happyReduce_54 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3600happyReduce_54 = happyReduce 8# 16# happyReduction_54
3601happyReduction_54 (happy_x_8 `HappyStk`
3602	happy_x_7 `HappyStk`
3603	happy_x_6 `HappyStk`
3604	happy_x_5 `HappyStk`
3605	happy_x_4 `HappyStk`
3606	happy_x_3 `HappyStk`
3607	happy_x_2 `HappyStk`
3608	happy_x_1 `HappyStk`
3609	happyRest)
3610	 = case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3611	case happyOutTok happy_x_2 of { happy_var_2 ->
3612	case happyOut65 happy_x_3 of { (HappyWrap65 happy_var_3) ->
3613	case happyOut319 happy_x_4 of { (HappyWrap319 happy_var_4) ->
3614	case happyOut38 happy_x_5 of { (HappyWrap38 happy_var_5) ->
3615	case happyOut48 happy_x_6 of { (HappyWrap48 happy_var_6) ->
3616	case happyOut39 happy_x_8 of { (HappyWrap39 happy_var_8) ->
3617	happyIn32
3618		 (sL1 happy_var_2 $ DeclD
3619                 (case snd happy_var_3 of
3620                   False -> HsSrcFile
3621                   True  -> HsBootFile)
3622                 happy_var_4
3623                 (Just $ sL1 happy_var_2 (HsModule (Just happy_var_4) happy_var_6 (fst $ snd happy_var_8) (snd $ snd happy_var_8) happy_var_5 happy_var_1))
3624	) `HappyStk` happyRest}}}}}}}
3625
3626happyReduce_55 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3627happyReduce_55 = happyReduce 7# 16# happyReduction_55
3628happyReduction_55 (happy_x_7 `HappyStk`
3629	happy_x_6 `HappyStk`
3630	happy_x_5 `HappyStk`
3631	happy_x_4 `HappyStk`
3632	happy_x_3 `HappyStk`
3633	happy_x_2 `HappyStk`
3634	happy_x_1 `HappyStk`
3635	happyRest)
3636	 = case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3637	case happyOutTok happy_x_2 of { happy_var_2 ->
3638	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3639	case happyOut38 happy_x_4 of { (HappyWrap38 happy_var_4) ->
3640	case happyOut48 happy_x_5 of { (HappyWrap48 happy_var_5) ->
3641	case happyOut39 happy_x_7 of { (HappyWrap39 happy_var_7) ->
3642	happyIn32
3643		 (sL1 happy_var_2 $ DeclD
3644                 HsigFile
3645                 happy_var_3
3646                 (Just $ sL1 happy_var_2 (HsModule (Just happy_var_3) happy_var_5 (fst $ snd happy_var_7) (snd $ snd happy_var_7) happy_var_4 happy_var_1))
3647	) `HappyStk` happyRest}}}}}}
3648
3649happyReduce_56 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3650happyReduce_56 = happyReduce 4# 16# happyReduction_56
3651happyReduction_56 (happy_x_4 `HappyStk`
3652	happy_x_3 `HappyStk`
3653	happy_x_2 `HappyStk`
3654	happy_x_1 `HappyStk`
3655	happyRest)
3656	 = case happyOutTok happy_x_2 of { happy_var_2 ->
3657	case happyOut65 happy_x_3 of { (HappyWrap65 happy_var_3) ->
3658	case happyOut319 happy_x_4 of { (HappyWrap319 happy_var_4) ->
3659	happyIn32
3660		 (sL1 happy_var_2 $ DeclD (case snd happy_var_3 of
3661                   False -> HsSrcFile
3662                   True  -> HsBootFile) happy_var_4 Nothing
3663	) `HappyStk` happyRest}}}
3664
3665happyReduce_57 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3666happyReduce_57 = happySpecReduce_3  16# happyReduction_57
3667happyReduction_57 happy_x_3
3668	happy_x_2
3669	happy_x_1
3670	 =  case happyOutTok happy_x_2 of { happy_var_2 ->
3671	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3672	happyIn32
3673		 (sL1 happy_var_2 $ DeclD HsigFile happy_var_3 Nothing
3674	)}}
3675
3676happyReduce_58 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3677happyReduce_58 = happySpecReduce_3  16# happyReduction_58
3678happyReduction_58 happy_x_3
3679	happy_x_2
3680	happy_x_1
3681	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3682	case happyOut20 happy_x_2 of { (HappyWrap20 happy_var_2) ->
3683	case happyOut27 happy_x_3 of { (HappyWrap27 happy_var_3) ->
3684	happyIn32
3685		 (sL1 happy_var_1 $ IncludeD (IncludeDecl { idUnitId = happy_var_2
3686                                              , idModRenaming = happy_var_3
3687                                              , idSignatureInclude = False })
3688	)}}}
3689
3690happyReduce_59 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3691happyReduce_59 = happySpecReduce_3  16# happyReduction_59
3692happyReduction_59 happy_x_3
3693	happy_x_2
3694	happy_x_1
3695	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3696	case happyOut20 happy_x_3 of { (HappyWrap20 happy_var_3) ->
3697	happyIn32
3698		 (sL1 happy_var_1 $ IncludeD (IncludeDecl { idUnitId = happy_var_3
3699                                              , idModRenaming = Nothing
3700                                              , idSignatureInclude = True })
3701	)}}
3702
3703happyReduce_60 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3704happyReduce_60 = happyMonadReduce 7# 17# happyReduction_60
3705happyReduction_60 (happy_x_7 `HappyStk`
3706	happy_x_6 `HappyStk`
3707	happy_x_5 `HappyStk`
3708	happy_x_4 `HappyStk`
3709	happy_x_3 `HappyStk`
3710	happy_x_2 `HappyStk`
3711	happy_x_1 `HappyStk`
3712	happyRest) tk
3713	 = happyThen ((case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3714	case happyOutTok happy_x_2 of { happy_var_2 ->
3715	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3716	case happyOut38 happy_x_4 of { (HappyWrap38 happy_var_4) ->
3717	case happyOut48 happy_x_5 of { (HappyWrap48 happy_var_5) ->
3718	case happyOutTok happy_x_6 of { happy_var_6 ->
3719	case happyOut39 happy_x_7 of { (HappyWrap39 happy_var_7) ->
3720	( fileSrcSpan >>= \ loc ->
3721                ams (cL loc (HsModule (Just happy_var_3) happy_var_5 (fst $ snd happy_var_7)
3722                              (snd $ snd happy_var_7) happy_var_4 happy_var_1)
3723                    )
3724                    ([mj AnnSignature happy_var_2, mj AnnWhere happy_var_6] ++ fst happy_var_7))}}}}}}})
3725	) (\r -> happyReturn (happyIn33 r))
3726
3727happyReduce_61 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3728happyReduce_61 = happyMonadReduce 7# 18# happyReduction_61
3729happyReduction_61 (happy_x_7 `HappyStk`
3730	happy_x_6 `HappyStk`
3731	happy_x_5 `HappyStk`
3732	happy_x_4 `HappyStk`
3733	happy_x_3 `HappyStk`
3734	happy_x_2 `HappyStk`
3735	happy_x_1 `HappyStk`
3736	happyRest) tk
3737	 = happyThen ((case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3738	case happyOutTok happy_x_2 of { happy_var_2 ->
3739	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3740	case happyOut38 happy_x_4 of { (HappyWrap38 happy_var_4) ->
3741	case happyOut48 happy_x_5 of { (HappyWrap48 happy_var_5) ->
3742	case happyOutTok happy_x_6 of { happy_var_6 ->
3743	case happyOut39 happy_x_7 of { (HappyWrap39 happy_var_7) ->
3744	( fileSrcSpan >>= \ loc ->
3745                ams (cL loc (HsModule (Just happy_var_3) happy_var_5 (fst $ snd happy_var_7)
3746                              (snd $ snd happy_var_7) happy_var_4 happy_var_1)
3747                    )
3748                    ([mj AnnModule happy_var_2, mj AnnWhere happy_var_6] ++ fst happy_var_7))}}}}}}})
3749	) (\r -> happyReturn (happyIn34 r))
3750
3751happyReduce_62 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3752happyReduce_62 = happyMonadReduce 1# 18# happyReduction_62
3753happyReduction_62 (happy_x_1 `HappyStk`
3754	happyRest) tk
3755	 = happyThen ((case happyOut40 happy_x_1 of { (HappyWrap40 happy_var_1) ->
3756	( fileSrcSpan >>= \ loc ->
3757                   ams (cL loc (HsModule Nothing Nothing
3758                               (fst $ snd happy_var_1) (snd $ snd happy_var_1) Nothing Nothing))
3759                       (fst happy_var_1))})
3760	) (\r -> happyReturn (happyIn34 r))
3761
3762happyReduce_63 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3763happyReduce_63 = happySpecReduce_1  19# happyReduction_63
3764happyReduction_63 happy_x_1
3765	 =  case happyOut327 happy_x_1 of { (HappyWrap327 happy_var_1) ->
3766	happyIn35
3767		 (happy_var_1
3768	)}
3769
3770happyReduce_64 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3771happyReduce_64 = happySpecReduce_0  19# happyReduction_64
3772happyReduction_64  =  happyIn35
3773		 (Nothing
3774	)
3775
3776happyReduce_65 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3777happyReduce_65 = happyMonadReduce 0# 20# happyReduction_65
3778happyReduction_65 (happyRest) tk
3779	 = happyThen ((( pushModuleContext))
3780	) (\r -> happyReturn (happyIn36 r))
3781
3782happyReduce_66 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3783happyReduce_66 = happyMonadReduce 0# 21# happyReduction_66
3784happyReduction_66 (happyRest) tk
3785	 = happyThen ((( pushModuleContext))
3786	) (\r -> happyReturn (happyIn37 r))
3787
3788happyReduce_67 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3789happyReduce_67 = happyMonadReduce 3# 22# happyReduction_67
3790happyReduction_67 (happy_x_3 `HappyStk`
3791	happy_x_2 `HappyStk`
3792	happy_x_1 `HappyStk`
3793	happyRest) tk
3794	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
3795	case happyOut140 happy_x_2 of { (HappyWrap140 happy_var_2) ->
3796	case happyOutTok happy_x_3 of { happy_var_3 ->
3797	( ajs (sLL happy_var_1 happy_var_3 $ DeprecatedTxt (sL1 happy_var_1 (getDEPRECATED_PRAGs happy_var_1)) (snd $ unLoc happy_var_2))
3798                             (mo happy_var_1:mc happy_var_3: (fst $ unLoc happy_var_2)))}}})
3799	) (\r -> happyReturn (happyIn38 r))
3800
3801happyReduce_68 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3802happyReduce_68 = happyMonadReduce 3# 22# happyReduction_68
3803happyReduction_68 (happy_x_3 `HappyStk`
3804	happy_x_2 `HappyStk`
3805	happy_x_1 `HappyStk`
3806	happyRest) tk
3807	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
3808	case happyOut140 happy_x_2 of { (HappyWrap140 happy_var_2) ->
3809	case happyOutTok happy_x_3 of { happy_var_3 ->
3810	( ajs (sLL happy_var_1 happy_var_3 $ WarningTxt (sL1 happy_var_1 (getWARNING_PRAGs happy_var_1)) (snd $ unLoc happy_var_2))
3811                                (mo happy_var_1:mc happy_var_3 : (fst $ unLoc happy_var_2)))}}})
3812	) (\r -> happyReturn (happyIn38 r))
3813
3814happyReduce_69 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3815happyReduce_69 = happySpecReduce_0  22# happyReduction_69
3816happyReduction_69  =  happyIn38
3817		 (Nothing
3818	)
3819
3820happyReduce_70 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3821happyReduce_70 = happySpecReduce_3  23# happyReduction_70
3822happyReduction_70 happy_x_3
3823	happy_x_2
3824	happy_x_1
3825	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3826	case happyOut41 happy_x_2 of { (HappyWrap41 happy_var_2) ->
3827	case happyOutTok happy_x_3 of { happy_var_3 ->
3828	happyIn39
3829		 ((moc happy_var_1:mcc happy_var_3:(fst happy_var_2)
3830                                         , snd happy_var_2)
3831	)}}}
3832
3833happyReduce_71 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3834happyReduce_71 = happySpecReduce_3  23# happyReduction_71
3835happyReduction_71 happy_x_3
3836	happy_x_2
3837	happy_x_1
3838	 =  case happyOut41 happy_x_2 of { (HappyWrap41 happy_var_2) ->
3839	happyIn39
3840		 ((fst happy_var_2, snd happy_var_2)
3841	)}
3842
3843happyReduce_72 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3844happyReduce_72 = happySpecReduce_3  24# happyReduction_72
3845happyReduction_72 happy_x_3
3846	happy_x_2
3847	happy_x_1
3848	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
3849	case happyOut41 happy_x_2 of { (HappyWrap41 happy_var_2) ->
3850	case happyOutTok happy_x_3 of { happy_var_3 ->
3851	happyIn40
3852		 ((moc happy_var_1:mcc happy_var_3
3853                                                   :(fst happy_var_2), snd happy_var_2)
3854	)}}}
3855
3856happyReduce_73 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3857happyReduce_73 = happySpecReduce_3  24# happyReduction_73
3858happyReduction_73 happy_x_3
3859	happy_x_2
3860	happy_x_1
3861	 =  case happyOut41 happy_x_2 of { (HappyWrap41 happy_var_2) ->
3862	happyIn40
3863		 (([],snd happy_var_2)
3864	)}
3865
3866happyReduce_74 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3867happyReduce_74 = happySpecReduce_2  25# happyReduction_74
3868happyReduction_74 happy_x_2
3869	happy_x_1
3870	 =  case happyOut61 happy_x_1 of { (HappyWrap61 happy_var_1) ->
3871	case happyOut42 happy_x_2 of { (HappyWrap42 happy_var_2) ->
3872	happyIn41
3873		 ((happy_var_1, happy_var_2)
3874	)}}
3875
3876happyReduce_75 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3877happyReduce_75 = happySpecReduce_2  26# happyReduction_75
3878happyReduction_75 happy_x_2
3879	happy_x_1
3880	 =  case happyOut63 happy_x_1 of { (HappyWrap63 happy_var_1) ->
3881	case happyOut76 happy_x_2 of { (HappyWrap76 happy_var_2) ->
3882	happyIn42
3883		 ((reverse happy_var_1, cvTopDecls happy_var_2)
3884	)}}
3885
3886happyReduce_76 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3887happyReduce_76 = happySpecReduce_2  26# happyReduction_76
3888happyReduction_76 happy_x_2
3889	happy_x_1
3890	 =  case happyOut63 happy_x_1 of { (HappyWrap63 happy_var_1) ->
3891	case happyOut75 happy_x_2 of { (HappyWrap75 happy_var_2) ->
3892	happyIn42
3893		 ((reverse happy_var_1, cvTopDecls happy_var_2)
3894	)}}
3895
3896happyReduce_77 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3897happyReduce_77 = happySpecReduce_1  26# happyReduction_77
3898happyReduction_77 happy_x_1
3899	 =  case happyOut62 happy_x_1 of { (HappyWrap62 happy_var_1) ->
3900	happyIn42
3901		 ((reverse happy_var_1, [])
3902	)}
3903
3904happyReduce_78 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3905happyReduce_78 = happyMonadReduce 7# 27# happyReduction_78
3906happyReduction_78 (happy_x_7 `HappyStk`
3907	happy_x_6 `HappyStk`
3908	happy_x_5 `HappyStk`
3909	happy_x_4 `HappyStk`
3910	happy_x_3 `HappyStk`
3911	happy_x_2 `HappyStk`
3912	happy_x_1 `HappyStk`
3913	happyRest) tk
3914	 = happyThen ((case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3915	case happyOutTok happy_x_2 of { happy_var_2 ->
3916	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3917	case happyOut38 happy_x_4 of { (HappyWrap38 happy_var_4) ->
3918	case happyOut48 happy_x_5 of { (HappyWrap48 happy_var_5) ->
3919	case happyOutTok happy_x_6 of { happy_var_6 ->
3920	case happyOut44 happy_x_7 of { (HappyWrap44 happy_var_7) ->
3921	( fileSrcSpan >>= \ loc ->
3922                   ams (cL loc (HsModule (Just happy_var_3) happy_var_5 happy_var_7 [] happy_var_4 happy_var_1
3923                          )) [mj AnnModule happy_var_2,mj AnnWhere happy_var_6])}}}}}}})
3924	) (\r -> happyReturn (happyIn43 r))
3925
3926happyReduce_79 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3927happyReduce_79 = happyMonadReduce 7# 27# happyReduction_79
3928happyReduction_79 (happy_x_7 `HappyStk`
3929	happy_x_6 `HappyStk`
3930	happy_x_5 `HappyStk`
3931	happy_x_4 `HappyStk`
3932	happy_x_3 `HappyStk`
3933	happy_x_2 `HappyStk`
3934	happy_x_1 `HappyStk`
3935	happyRest) tk
3936	 = happyThen ((case happyOut35 happy_x_1 of { (HappyWrap35 happy_var_1) ->
3937	case happyOutTok happy_x_2 of { happy_var_2 ->
3938	case happyOut319 happy_x_3 of { (HappyWrap319 happy_var_3) ->
3939	case happyOut38 happy_x_4 of { (HappyWrap38 happy_var_4) ->
3940	case happyOut48 happy_x_5 of { (HappyWrap48 happy_var_5) ->
3941	case happyOutTok happy_x_6 of { happy_var_6 ->
3942	case happyOut44 happy_x_7 of { (HappyWrap44 happy_var_7) ->
3943	( fileSrcSpan >>= \ loc ->
3944                   ams (cL loc (HsModule (Just happy_var_3) happy_var_5 happy_var_7 [] happy_var_4 happy_var_1
3945                          )) [mj AnnModule happy_var_2,mj AnnWhere happy_var_6])}}}}}}})
3946	) (\r -> happyReturn (happyIn43 r))
3947
3948happyReduce_80 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3949happyReduce_80 = happyMonadReduce 1# 27# happyReduction_80
3950happyReduction_80 (happy_x_1 `HappyStk`
3951	happyRest) tk
3952	 = happyThen ((case happyOut45 happy_x_1 of { (HappyWrap45 happy_var_1) ->
3953	( fileSrcSpan >>= \ loc ->
3954                   return (cL loc (HsModule Nothing Nothing happy_var_1 [] Nothing
3955                          Nothing)))})
3956	) (\r -> happyReturn (happyIn43 r))
3957
3958happyReduce_81 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3959happyReduce_81 = happySpecReduce_2  28# happyReduction_81
3960happyReduction_81 happy_x_2
3961	happy_x_1
3962	 =  case happyOut46 happy_x_2 of { (HappyWrap46 happy_var_2) ->
3963	happyIn44
3964		 (happy_var_2
3965	)}
3966
3967happyReduce_82 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3968happyReduce_82 = happySpecReduce_2  28# happyReduction_82
3969happyReduction_82 happy_x_2
3970	happy_x_1
3971	 =  case happyOut46 happy_x_2 of { (HappyWrap46 happy_var_2) ->
3972	happyIn44
3973		 (happy_var_2
3974	)}
3975
3976happyReduce_83 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3977happyReduce_83 = happySpecReduce_2  29# happyReduction_83
3978happyReduction_83 happy_x_2
3979	happy_x_1
3980	 =  case happyOut46 happy_x_2 of { (HappyWrap46 happy_var_2) ->
3981	happyIn45
3982		 (happy_var_2
3983	)}
3984
3985happyReduce_84 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3986happyReduce_84 = happySpecReduce_2  29# happyReduction_84
3987happyReduction_84 happy_x_2
3988	happy_x_1
3989	 =  case happyOut46 happy_x_2 of { (HappyWrap46 happy_var_2) ->
3990	happyIn45
3991		 (happy_var_2
3992	)}
3993
3994happyReduce_85 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
3995happyReduce_85 = happySpecReduce_2  30# happyReduction_85
3996happyReduction_85 happy_x_2
3997	happy_x_1
3998	 =  case happyOut47 happy_x_2 of { (HappyWrap47 happy_var_2) ->
3999	happyIn46
4000		 (happy_var_2
4001	)}
4002
4003happyReduce_86 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4004happyReduce_86 = happySpecReduce_1  31# happyReduction_86
4005happyReduction_86 happy_x_1
4006	 =  case happyOut63 happy_x_1 of { (HappyWrap63 happy_var_1) ->
4007	happyIn47
4008		 (happy_var_1
4009	)}
4010
4011happyReduce_87 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4012happyReduce_87 = happySpecReduce_1  31# happyReduction_87
4013happyReduction_87 happy_x_1
4014	 =  case happyOut62 happy_x_1 of { (HappyWrap62 happy_var_1) ->
4015	happyIn47
4016		 (happy_var_1
4017	)}
4018
4019happyReduce_88 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4020happyReduce_88 = happyMonadReduce 3# 32# happyReduction_88
4021happyReduction_88 (happy_x_3 `HappyStk`
4022	happy_x_2 `HappyStk`
4023	happy_x_1 `HappyStk`
4024	happyRest) tk
4025	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4026	case happyOut49 happy_x_2 of { (HappyWrap49 happy_var_2) ->
4027	case happyOutTok happy_x_3 of { happy_var_3 ->
4028	( amsL (comb2 happy_var_1 happy_var_3) [mop happy_var_1,mcp happy_var_3] >>
4029                                       return (Just (sLL happy_var_1 happy_var_3 (fromOL happy_var_2))))}}})
4030	) (\r -> happyReturn (happyIn48 r))
4031
4032happyReduce_89 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4033happyReduce_89 = happySpecReduce_0  32# happyReduction_89
4034happyReduction_89  =  happyIn48
4035		 (Nothing
4036	)
4037
4038happyReduce_90 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4039happyReduce_90 = happyMonadReduce 3# 33# happyReduction_90
4040happyReduction_90 (happy_x_3 `HappyStk`
4041	happy_x_2 `HappyStk`
4042	happy_x_1 `HappyStk`
4043	happyRest) tk
4044	 = happyThen ((case happyOut51 happy_x_1 of { (HappyWrap51 happy_var_1) ->
4045	case happyOutTok happy_x_2 of { happy_var_2 ->
4046	case happyOut51 happy_x_3 of { (HappyWrap51 happy_var_3) ->
4047	( addAnnotation (oll happy_var_1) AnnComma (gl happy_var_2)
4048                                         >> return (happy_var_1 `appOL` happy_var_3))}}})
4049	) (\r -> happyReturn (happyIn49 r))
4050
4051happyReduce_91 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4052happyReduce_91 = happySpecReduce_1  33# happyReduction_91
4053happyReduction_91 happy_x_1
4054	 =  case happyOut50 happy_x_1 of { (HappyWrap50 happy_var_1) ->
4055	happyIn49
4056		 (happy_var_1
4057	)}
4058
4059happyReduce_92 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4060happyReduce_92 = happyMonadReduce 5# 34# happyReduction_92
4061happyReduction_92 (happy_x_5 `HappyStk`
4062	happy_x_4 `HappyStk`
4063	happy_x_3 `HappyStk`
4064	happy_x_2 `HappyStk`
4065	happy_x_1 `HappyStk`
4066	happyRest) tk
4067	 = happyThen ((case happyOut51 happy_x_1 of { (HappyWrap51 happy_var_1) ->
4068	case happyOut53 happy_x_2 of { (HappyWrap53 happy_var_2) ->
4069	case happyOut51 happy_x_3 of { (HappyWrap51 happy_var_3) ->
4070	case happyOutTok happy_x_4 of { happy_var_4 ->
4071	case happyOut50 happy_x_5 of { (HappyWrap50 happy_var_5) ->
4072	( (addAnnotation (oll (happy_var_1 `appOL` happy_var_2 `appOL` happy_var_3))
4073                                            AnnComma (gl happy_var_4) ) >>
4074                              return (happy_var_1 `appOL` happy_var_2 `appOL` happy_var_3 `appOL` happy_var_5))}}}}})
4075	) (\r -> happyReturn (happyIn50 r))
4076
4077happyReduce_93 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4078happyReduce_93 = happySpecReduce_3  34# happyReduction_93
4079happyReduction_93 happy_x_3
4080	happy_x_2
4081	happy_x_1
4082	 =  case happyOut51 happy_x_1 of { (HappyWrap51 happy_var_1) ->
4083	case happyOut53 happy_x_2 of { (HappyWrap53 happy_var_2) ->
4084	case happyOut51 happy_x_3 of { (HappyWrap51 happy_var_3) ->
4085	happyIn50
4086		 (happy_var_1 `appOL` happy_var_2 `appOL` happy_var_3
4087	)}}}
4088
4089happyReduce_94 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4090happyReduce_94 = happySpecReduce_1  34# happyReduction_94
4091happyReduction_94 happy_x_1
4092	 =  case happyOut51 happy_x_1 of { (HappyWrap51 happy_var_1) ->
4093	happyIn50
4094		 (happy_var_1
4095	)}
4096
4097happyReduce_95 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4098happyReduce_95 = happySpecReduce_2  35# happyReduction_95
4099happyReduction_95 happy_x_2
4100	happy_x_1
4101	 =  case happyOut52 happy_x_1 of { (HappyWrap52 happy_var_1) ->
4102	case happyOut51 happy_x_2 of { (HappyWrap51 happy_var_2) ->
4103	happyIn51
4104		 (happy_var_1 `appOL` happy_var_2
4105	)}}
4106
4107happyReduce_96 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4108happyReduce_96 = happySpecReduce_0  35# happyReduction_96
4109happyReduction_96  =  happyIn51
4110		 (nilOL
4111	)
4112
4113happyReduce_97 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4114happyReduce_97 = happySpecReduce_1  36# happyReduction_97
4115happyReduction_97 happy_x_1
4116	 =  case happyOut326 happy_x_1 of { (HappyWrap326 happy_var_1) ->
4117	happyIn52
4118		 (unitOL (sL1 happy_var_1 (case (unLoc happy_var_1) of (n, doc) -> IEGroup noExtField n doc))
4119	)}
4120
4121happyReduce_98 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4122happyReduce_98 = happySpecReduce_1  36# happyReduction_98
4123happyReduction_98 happy_x_1
4124	 =  case happyOut325 happy_x_1 of { (HappyWrap325 happy_var_1) ->
4125	happyIn52
4126		 (unitOL (sL1 happy_var_1 (IEDocNamed noExtField ((fst . unLoc) happy_var_1)))
4127	)}
4128
4129happyReduce_99 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4130happyReduce_99 = happySpecReduce_1  36# happyReduction_99
4131happyReduction_99 happy_x_1
4132	 =  case happyOut323 happy_x_1 of { (HappyWrap323 happy_var_1) ->
4133	happyIn52
4134		 (unitOL (sL1 happy_var_1 (IEDoc noExtField (unLoc happy_var_1)))
4135	)}
4136
4137happyReduce_100 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4138happyReduce_100 = happyMonadReduce 2# 37# happyReduction_100
4139happyReduction_100 (happy_x_2 `HappyStk`
4140	happy_x_1 `HappyStk`
4141	happyRest) tk
4142	 = happyThen ((case happyOut58 happy_x_1 of { (HappyWrap58 happy_var_1) ->
4143	case happyOut54 happy_x_2 of { (HappyWrap54 happy_var_2) ->
4144	( mkModuleImpExp happy_var_1 (snd $ unLoc happy_var_2)
4145                                          >>= \ie -> amsu (sLL happy_var_1 happy_var_2 ie) (fst $ unLoc happy_var_2))}})
4146	) (\r -> happyReturn (happyIn53 r))
4147
4148happyReduce_101 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4149happyReduce_101 = happyMonadReduce 2# 37# happyReduction_101
4150happyReduction_101 (happy_x_2 `HappyStk`
4151	happy_x_1 `HappyStk`
4152	happyRest) tk
4153	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4154	case happyOut319 happy_x_2 of { (HappyWrap319 happy_var_2) ->
4155	( amsu (sLL happy_var_1 happy_var_2 (IEModuleContents noExtField happy_var_2))
4156                                             [mj AnnModule happy_var_1])}})
4157	) (\r -> happyReturn (happyIn53 r))
4158
4159happyReduce_102 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4160happyReduce_102 = happyMonadReduce 2# 37# happyReduction_102
4161happyReduction_102 (happy_x_2 `HappyStk`
4162	happy_x_1 `HappyStk`
4163	happyRest) tk
4164	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4165	case happyOut274 happy_x_2 of { (HappyWrap274 happy_var_2) ->
4166	( amsu (sLL happy_var_1 happy_var_2 (IEVar noExtField (sLL happy_var_1 happy_var_2 (IEPattern happy_var_2))))
4167                                             [mj AnnPattern happy_var_1])}})
4168	) (\r -> happyReturn (happyIn53 r))
4169
4170happyReduce_103 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4171happyReduce_103 = happySpecReduce_0  38# happyReduction_103
4172happyReduction_103  =  happyIn54
4173		 (sL0 ([],ImpExpAbs)
4174	)
4175
4176happyReduce_104 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4177happyReduce_104 = happyMonadReduce 3# 38# happyReduction_104
4178happyReduction_104 (happy_x_3 `HappyStk`
4179	happy_x_2 `HappyStk`
4180	happy_x_1 `HappyStk`
4181	happyRest) tk
4182	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4183	case happyOut55 happy_x_2 of { (HappyWrap55 happy_var_2) ->
4184	case happyOutTok happy_x_3 of { happy_var_3 ->
4185	( mkImpExpSubSpec (reverse (snd happy_var_2))
4186                                      >>= \(as,ie) -> return $ sLL happy_var_1 happy_var_3
4187                                            (as ++ [mop happy_var_1,mcp happy_var_3] ++ fst happy_var_2, ie))}}})
4188	) (\r -> happyReturn (happyIn54 r))
4189
4190happyReduce_105 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4191happyReduce_105 = happySpecReduce_0  39# happyReduction_105
4192happyReduction_105  =  happyIn55
4193		 (([],[])
4194	)
4195
4196happyReduce_106 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4197happyReduce_106 = happySpecReduce_1  39# happyReduction_106
4198happyReduction_106 happy_x_1
4199	 =  case happyOut56 happy_x_1 of { (HappyWrap56 happy_var_1) ->
4200	happyIn55
4201		 (happy_var_1
4202	)}
4203
4204happyReduce_107 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4205happyReduce_107 = happyMonadReduce 3# 40# happyReduction_107
4206happyReduction_107 (happy_x_3 `HappyStk`
4207	happy_x_2 `HappyStk`
4208	happy_x_1 `HappyStk`
4209	happyRest) tk
4210	 = happyThen ((case happyOut56 happy_x_1 of { (HappyWrap56 happy_var_1) ->
4211	case happyOutTok happy_x_2 of { happy_var_2 ->
4212	case happyOut57 happy_x_3 of { (HappyWrap57 happy_var_3) ->
4213	( case (head (snd happy_var_1)) of
4214                                                    l@(dL->L _ ImpExpQcWildcard) ->
4215                                                       return ([mj AnnComma happy_var_2, mj AnnDotdot l]
4216                                                               ,(snd (unLoc happy_var_3)  : snd happy_var_1))
4217                                                    l -> (ams (head (snd happy_var_1)) [mj AnnComma happy_var_2] >>
4218                                                          return (fst happy_var_1 ++ fst (unLoc happy_var_3),
4219                                                                  snd (unLoc happy_var_3) : snd happy_var_1)))}}})
4220	) (\r -> happyReturn (happyIn56 r))
4221
4222happyReduce_108 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4223happyReduce_108 = happySpecReduce_1  40# happyReduction_108
4224happyReduction_108 happy_x_1
4225	 =  case happyOut57 happy_x_1 of { (HappyWrap57 happy_var_1) ->
4226	happyIn56
4227		 ((fst (unLoc happy_var_1),[snd (unLoc happy_var_1)])
4228	)}
4229
4230happyReduce_109 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4231happyReduce_109 = happySpecReduce_1  41# happyReduction_109
4232happyReduction_109 happy_x_1
4233	 =  case happyOut58 happy_x_1 of { (HappyWrap58 happy_var_1) ->
4234	happyIn57
4235		 (sL1 happy_var_1 ([],happy_var_1)
4236	)}
4237
4238happyReduce_110 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4239happyReduce_110 = happySpecReduce_1  41# happyReduction_110
4240happyReduction_110 happy_x_1
4241	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4242	happyIn57
4243		 (sL1 happy_var_1 ([mj AnnDotdot happy_var_1], sL1 happy_var_1 ImpExpQcWildcard)
4244	)}
4245
4246happyReduce_111 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4247happyReduce_111 = happySpecReduce_1  42# happyReduction_111
4248happyReduction_111 happy_x_1
4249	 =  case happyOut59 happy_x_1 of { (HappyWrap59 happy_var_1) ->
4250	happyIn58
4251		 (sL1 happy_var_1 (ImpExpQcName happy_var_1)
4252	)}
4253
4254happyReduce_112 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4255happyReduce_112 = happyMonadReduce 2# 42# happyReduction_112
4256happyReduction_112 (happy_x_2 `HappyStk`
4257	happy_x_1 `HappyStk`
4258	happyRest) tk
4259	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4260	case happyOut284 happy_x_2 of { (HappyWrap284 happy_var_2) ->
4261	( do { n <- mkTypeImpExp happy_var_2
4262                                          ; ams (sLL happy_var_1 happy_var_2 (ImpExpQcType n))
4263                                                [mj AnnType happy_var_1] })}})
4264	) (\r -> happyReturn (happyIn58 r))
4265
4266happyReduce_113 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4267happyReduce_113 = happySpecReduce_1  43# happyReduction_113
4268happyReduction_113 happy_x_1
4269	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
4270	happyIn59
4271		 (happy_var_1
4272	)}
4273
4274happyReduce_114 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4275happyReduce_114 = happySpecReduce_1  43# happyReduction_114
4276happyReduction_114 happy_x_1
4277	 =  case happyOut285 happy_x_1 of { (HappyWrap285 happy_var_1) ->
4278	happyIn59
4279		 (happy_var_1
4280	)}
4281
4282happyReduce_115 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4283happyReduce_115 = happySpecReduce_2  44# happyReduction_115
4284happyReduction_115 happy_x_2
4285	happy_x_1
4286	 =  case happyOut60 happy_x_1 of { (HappyWrap60 happy_var_1) ->
4287	case happyOutTok happy_x_2 of { happy_var_2 ->
4288	happyIn60
4289		 (mj AnnSemi happy_var_2 : happy_var_1
4290	)}}
4291
4292happyReduce_116 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4293happyReduce_116 = happySpecReduce_1  44# happyReduction_116
4294happyReduction_116 happy_x_1
4295	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4296	happyIn60
4297		 ([mj AnnSemi happy_var_1]
4298	)}
4299
4300happyReduce_117 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4301happyReduce_117 = happySpecReduce_2  45# happyReduction_117
4302happyReduction_117 happy_x_2
4303	happy_x_1
4304	 =  case happyOut61 happy_x_1 of { (HappyWrap61 happy_var_1) ->
4305	case happyOutTok happy_x_2 of { happy_var_2 ->
4306	happyIn61
4307		 (mj AnnSemi happy_var_2 : happy_var_1
4308	)}}
4309
4310happyReduce_118 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4311happyReduce_118 = happySpecReduce_0  45# happyReduction_118
4312happyReduction_118  =  happyIn61
4313		 ([]
4314	)
4315
4316happyReduce_119 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4317happyReduce_119 = happySpecReduce_2  46# happyReduction_119
4318happyReduction_119 happy_x_2
4319	happy_x_1
4320	 =  case happyOut63 happy_x_1 of { (HappyWrap63 happy_var_1) ->
4321	case happyOut64 happy_x_2 of { (HappyWrap64 happy_var_2) ->
4322	happyIn62
4323		 (happy_var_2 : happy_var_1
4324	)}}
4325
4326happyReduce_120 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4327happyReduce_120 = happyMonadReduce 3# 47# happyReduction_120
4328happyReduction_120 (happy_x_3 `HappyStk`
4329	happy_x_2 `HappyStk`
4330	happy_x_1 `HappyStk`
4331	happyRest) tk
4332	 = happyThen ((case happyOut63 happy_x_1 of { (HappyWrap63 happy_var_1) ->
4333	case happyOut64 happy_x_2 of { (HappyWrap64 happy_var_2) ->
4334	case happyOut60 happy_x_3 of { (HappyWrap60 happy_var_3) ->
4335	( ams happy_var_2 happy_var_3 >> return (happy_var_2 : happy_var_1))}}})
4336	) (\r -> happyReturn (happyIn63 r))
4337
4338happyReduce_121 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4339happyReduce_121 = happySpecReduce_0  47# happyReduction_121
4340happyReduction_121  =  happyIn63
4341		 ([]
4342	)
4343
4344happyReduce_122 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4345happyReduce_122 = happyMonadReduce 9# 48# happyReduction_122
4346happyReduction_122 (happy_x_9 `HappyStk`
4347	happy_x_8 `HappyStk`
4348	happy_x_7 `HappyStk`
4349	happy_x_6 `HappyStk`
4350	happy_x_5 `HappyStk`
4351	happy_x_4 `HappyStk`
4352	happy_x_3 `HappyStk`
4353	happy_x_2 `HappyStk`
4354	happy_x_1 `HappyStk`
4355	happyRest) tk
4356	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4357	case happyOut65 happy_x_2 of { (HappyWrap65 happy_var_2) ->
4358	case happyOut66 happy_x_3 of { (HappyWrap66 happy_var_3) ->
4359	case happyOut68 happy_x_4 of { (HappyWrap68 happy_var_4) ->
4360	case happyOut67 happy_x_5 of { (HappyWrap67 happy_var_5) ->
4361	case happyOut319 happy_x_6 of { (HappyWrap319 happy_var_6) ->
4362	case happyOut68 happy_x_7 of { (HappyWrap68 happy_var_7) ->
4363	case happyOut69 happy_x_8 of { (HappyWrap69 happy_var_8) ->
4364	case happyOut70 happy_x_9 of { (HappyWrap70 happy_var_9) ->
4365	( do {
4366                  ; let { ; mPreQual = unLoc happy_var_4
4367                          ; mPostQual = unLoc happy_var_7 }
4368                  ; checkImportDecl mPreQual mPostQual
4369                  ; ams (cL (comb5 happy_var_1 happy_var_6 happy_var_7 (snd happy_var_8) happy_var_9) $
4370                      ImportDecl { ideclExt = noExtField
4371                                  , ideclSourceSrc = snd $ fst happy_var_2
4372                                  , ideclName = happy_var_6, ideclPkgQual = snd happy_var_5
4373                                  , ideclSource = snd happy_var_2, ideclSafe = snd happy_var_3
4374                                  , ideclQualified = importDeclQualifiedStyle mPreQual mPostQual
4375                                  , ideclImplicit = False
4376                                  , ideclAs = unLoc (snd happy_var_8)
4377                                  , ideclHiding = unLoc happy_var_9 })
4378                         (mj AnnImport happy_var_1 : fst (fst happy_var_2) ++ fst happy_var_3 ++ fmap (mj AnnQualified) (maybeToList mPreQual)
4379                                          ++ fst happy_var_5 ++ fmap (mj AnnQualified) (maybeToList mPostQual) ++ fst happy_var_8)
4380                  })}}}}}}}}})
4381	) (\r -> happyReturn (happyIn64 r))
4382
4383happyReduce_123 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4384happyReduce_123 = happySpecReduce_2  49# happyReduction_123
4385happyReduction_123 happy_x_2
4386	happy_x_1
4387	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4388	case happyOutTok happy_x_2 of { happy_var_2 ->
4389	happyIn65
4390		 ((([mo happy_var_1,mc happy_var_2],getSOURCE_PRAGs happy_var_1)
4391                                      , True)
4392	)}}
4393
4394happyReduce_124 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4395happyReduce_124 = happySpecReduce_0  49# happyReduction_124
4396happyReduction_124  =  happyIn65
4397		 ((([],NoSourceText),False)
4398	)
4399
4400happyReduce_125 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4401happyReduce_125 = happySpecReduce_1  50# happyReduction_125
4402happyReduction_125 happy_x_1
4403	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4404	happyIn66
4405		 (([mj AnnSafe happy_var_1],True)
4406	)}
4407
4408happyReduce_126 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4409happyReduce_126 = happySpecReduce_0  50# happyReduction_126
4410happyReduction_126  =  happyIn66
4411		 (([],False)
4412	)
4413
4414happyReduce_127 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4415happyReduce_127 = happyMonadReduce 1# 51# happyReduction_127
4416happyReduction_127 (happy_x_1 `HappyStk`
4417	happyRest) tk
4418	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4419	( do { let { pkgFS = getSTRING happy_var_1 }
4420                        ; unless (looksLikePackageName (unpackFS pkgFS)) $
4421                             addError (getLoc happy_var_1) $ vcat [
4422                             text "Parse error" <> colon <+> quotes (ppr pkgFS),
4423                             text "Version number or non-alphanumeric" <+>
4424                             text "character in package name"]
4425                        ; return ([mj AnnPackageName happy_var_1], Just (StringLiteral (getSTRINGs happy_var_1) pkgFS)) })})
4426	) (\r -> happyReturn (happyIn67 r))
4427
4428happyReduce_128 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4429happyReduce_128 = happySpecReduce_0  51# happyReduction_128
4430happyReduction_128  =  happyIn67
4431		 (([],Nothing)
4432	)
4433
4434happyReduce_129 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4435happyReduce_129 = happySpecReduce_1  52# happyReduction_129
4436happyReduction_129 happy_x_1
4437	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4438	happyIn68
4439		 (sL1 happy_var_1 (Just happy_var_1)
4440	)}
4441
4442happyReduce_130 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4443happyReduce_130 = happySpecReduce_0  52# happyReduction_130
4444happyReduction_130  =  happyIn68
4445		 (noLoc Nothing
4446	)
4447
4448happyReduce_131 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4449happyReduce_131 = happySpecReduce_2  53# happyReduction_131
4450happyReduction_131 happy_x_2
4451	happy_x_1
4452	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4453	case happyOut319 happy_x_2 of { (HappyWrap319 happy_var_2) ->
4454	happyIn69
4455		 (([mj AnnAs happy_var_1]
4456                                                 ,sLL happy_var_1 happy_var_2 (Just happy_var_2))
4457	)}}
4458
4459happyReduce_132 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4460happyReduce_132 = happySpecReduce_0  53# happyReduction_132
4461happyReduction_132  =  happyIn69
4462		 (([],noLoc Nothing)
4463	)
4464
4465happyReduce_133 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4466happyReduce_133 = happyMonadReduce 1# 54# happyReduction_133
4467happyReduction_133 (happy_x_1 `HappyStk`
4468	happyRest) tk
4469	 = happyThen ((case happyOut71 happy_x_1 of { (HappyWrap71 happy_var_1) ->
4470	( let (b, ie) = unLoc happy_var_1 in
4471                                       checkImportSpec ie
4472                                        >>= \checkedIe ->
4473                                          return (cL (gl happy_var_1) (Just (b, checkedIe))))})
4474	) (\r -> happyReturn (happyIn70 r))
4475
4476happyReduce_134 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4477happyReduce_134 = happySpecReduce_0  54# happyReduction_134
4478happyReduction_134  =  happyIn70
4479		 (noLoc Nothing
4480	)
4481
4482happyReduce_135 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4483happyReduce_135 = happyMonadReduce 3# 55# happyReduction_135
4484happyReduction_135 (happy_x_3 `HappyStk`
4485	happy_x_2 `HappyStk`
4486	happy_x_1 `HappyStk`
4487	happyRest) tk
4488	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4489	case happyOut49 happy_x_2 of { (HappyWrap49 happy_var_2) ->
4490	case happyOutTok happy_x_3 of { happy_var_3 ->
4491	( ams (sLL happy_var_1 happy_var_3 (False,
4492                                                      sLL happy_var_1 happy_var_3 $ fromOL happy_var_2))
4493                                                   [mop happy_var_1,mcp happy_var_3])}}})
4494	) (\r -> happyReturn (happyIn71 r))
4495
4496happyReduce_136 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4497happyReduce_136 = happyMonadReduce 4# 55# happyReduction_136
4498happyReduction_136 (happy_x_4 `HappyStk`
4499	happy_x_3 `HappyStk`
4500	happy_x_2 `HappyStk`
4501	happy_x_1 `HappyStk`
4502	happyRest) tk
4503	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4504	case happyOutTok happy_x_2 of { happy_var_2 ->
4505	case happyOut49 happy_x_3 of { (HappyWrap49 happy_var_3) ->
4506	case happyOutTok happy_x_4 of { happy_var_4 ->
4507	( ams (sLL happy_var_1 happy_var_4 (True,
4508                                                      sLL happy_var_1 happy_var_4 $ fromOL happy_var_3))
4509                                               [mj AnnHiding happy_var_1,mop happy_var_2,mcp happy_var_4])}}}})
4510	) (\r -> happyReturn (happyIn71 r))
4511
4512happyReduce_137 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4513happyReduce_137 = happySpecReduce_0  56# happyReduction_137
4514happyReduction_137  =  happyIn72
4515		 (noLoc (NoSourceText,9)
4516	)
4517
4518happyReduce_138 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4519happyReduce_138 = happySpecReduce_1  56# happyReduction_138
4520happyReduction_138 happy_x_1
4521	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4522	happyIn72
4523		 (sL1 happy_var_1 (getINTEGERs happy_var_1,fromInteger (il_value (getINTEGER happy_var_1)))
4524	)}
4525
4526happyReduce_139 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4527happyReduce_139 = happySpecReduce_1  57# happyReduction_139
4528happyReduction_139 happy_x_1
4529	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4530	happyIn73
4531		 (sL1 happy_var_1 InfixN
4532	)}
4533
4534happyReduce_140 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4535happyReduce_140 = happySpecReduce_1  57# happyReduction_140
4536happyReduction_140 happy_x_1
4537	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4538	happyIn73
4539		 (sL1 happy_var_1 InfixL
4540	)}
4541
4542happyReduce_141 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4543happyReduce_141 = happySpecReduce_1  57# happyReduction_141
4544happyReduction_141 happy_x_1
4545	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
4546	happyIn73
4547		 (sL1 happy_var_1 InfixR
4548	)}
4549
4550happyReduce_142 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4551happyReduce_142 = happyMonadReduce 3# 58# happyReduction_142
4552happyReduction_142 (happy_x_3 `HappyStk`
4553	happy_x_2 `HappyStk`
4554	happy_x_1 `HappyStk`
4555	happyRest) tk
4556	 = happyThen ((case happyOut74 happy_x_1 of { (HappyWrap74 happy_var_1) ->
4557	case happyOutTok happy_x_2 of { happy_var_2 ->
4558	case happyOut292 happy_x_3 of { (HappyWrap292 happy_var_3) ->
4559	( addAnnotation (oll $ unLoc happy_var_1) AnnComma (gl happy_var_2) >>
4560                              return (sLL happy_var_1 happy_var_3 ((unLoc happy_var_1) `appOL` unitOL happy_var_3)))}}})
4561	) (\r -> happyReturn (happyIn74 r))
4562
4563happyReduce_143 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4564happyReduce_143 = happySpecReduce_1  58# happyReduction_143
4565happyReduction_143 happy_x_1
4566	 =  case happyOut292 happy_x_1 of { (HappyWrap292 happy_var_1) ->
4567	happyIn74
4568		 (sL1 happy_var_1 (unitOL happy_var_1)
4569	)}
4570
4571happyReduce_144 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4572happyReduce_144 = happySpecReduce_2  59# happyReduction_144
4573happyReduction_144 happy_x_2
4574	happy_x_1
4575	 =  case happyOut76 happy_x_1 of { (HappyWrap76 happy_var_1) ->
4576	case happyOut77 happy_x_2 of { (HappyWrap77 happy_var_2) ->
4577	happyIn75
4578		 (happy_var_1 `snocOL` happy_var_2
4579	)}}
4580
4581happyReduce_145 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4582happyReduce_145 = happyMonadReduce 3# 60# happyReduction_145
4583happyReduction_145 (happy_x_3 `HappyStk`
4584	happy_x_2 `HappyStk`
4585	happy_x_1 `HappyStk`
4586	happyRest) tk
4587	 = happyThen ((case happyOut76 happy_x_1 of { (HappyWrap76 happy_var_1) ->
4588	case happyOut77 happy_x_2 of { (HappyWrap77 happy_var_2) ->
4589	case happyOut60 happy_x_3 of { (HappyWrap60 happy_var_3) ->
4590	( ams happy_var_2 happy_var_3 >> return (happy_var_1 `snocOL` happy_var_2))}}})
4591	) (\r -> happyReturn (happyIn76 r))
4592
4593happyReduce_146 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4594happyReduce_146 = happySpecReduce_0  60# happyReduction_146
4595happyReduction_146  =  happyIn76
4596		 (nilOL
4597	)
4598
4599happyReduce_147 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4600happyReduce_147 = happySpecReduce_1  61# happyReduction_147
4601happyReduction_147 happy_x_1
4602	 =  case happyOut78 happy_x_1 of { (HappyWrap78 happy_var_1) ->
4603	happyIn77
4604		 (sL1 happy_var_1 (TyClD noExtField (unLoc happy_var_1))
4605	)}
4606
4607happyReduce_148 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4608happyReduce_148 = happySpecReduce_1  61# happyReduction_148
4609happyReduction_148 happy_x_1
4610	 =  case happyOut79 happy_x_1 of { (HappyWrap79 happy_var_1) ->
4611	happyIn77
4612		 (sL1 happy_var_1 (TyClD noExtField (unLoc happy_var_1))
4613	)}
4614
4615happyReduce_149 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4616happyReduce_149 = happySpecReduce_1  61# happyReduction_149
4617happyReduction_149 happy_x_1
4618	 =  case happyOut80 happy_x_1 of { (HappyWrap80 happy_var_1) ->
4619	happyIn77
4620		 (sL1 happy_var_1 (KindSigD noExtField (unLoc happy_var_1))
4621	)}
4622
4623happyReduce_150 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4624happyReduce_150 = happySpecReduce_1  61# happyReduction_150
4625happyReduction_150 happy_x_1
4626	 =  case happyOut82 happy_x_1 of { (HappyWrap82 happy_var_1) ->
4627	happyIn77
4628		 (sL1 happy_var_1 (InstD noExtField (unLoc happy_var_1))
4629	)}
4630
4631happyReduce_151 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4632happyReduce_151 = happySpecReduce_1  61# happyReduction_151
4633happyReduction_151 happy_x_1
4634	 =  case happyOut106 happy_x_1 of { (HappyWrap106 happy_var_1) ->
4635	happyIn77
4636		 (sLL happy_var_1 happy_var_1 (DerivD noExtField (unLoc happy_var_1))
4637	)}
4638
4639happyReduce_152 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4640happyReduce_152 = happySpecReduce_1  61# happyReduction_152
4641happyReduction_152 happy_x_1
4642	 =  case happyOut107 happy_x_1 of { (HappyWrap107 happy_var_1) ->
4643	happyIn77
4644		 (sL1 happy_var_1 (RoleAnnotD noExtField (unLoc happy_var_1))
4645	)}
4646
4647happyReduce_153 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4648happyReduce_153 = happyMonadReduce 4# 61# happyReduction_153
4649happyReduction_153 (happy_x_4 `HappyStk`
4650	happy_x_3 `HappyStk`
4651	happy_x_2 `HappyStk`
4652	happy_x_1 `HappyStk`
4653	happyRest) tk
4654	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4655	case happyOutTok happy_x_2 of { happy_var_2 ->
4656	case happyOut172 happy_x_3 of { (HappyWrap172 happy_var_3) ->
4657	case happyOutTok happy_x_4 of { happy_var_4 ->
4658	( ams (sLL happy_var_1 happy_var_4 (DefD noExtField (DefaultDecl noExtField happy_var_3)))
4659                                                         [mj AnnDefault happy_var_1
4660                                                         ,mop happy_var_2,mcp happy_var_4])}}}})
4661	) (\r -> happyReturn (happyIn77 r))
4662
4663happyReduce_154 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4664happyReduce_154 = happyMonadReduce 2# 61# happyReduction_154
4665happyReduction_154 (happy_x_2 `HappyStk`
4666	happy_x_1 `HappyStk`
4667	happyRest) tk
4668	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4669	case happyOut143 happy_x_2 of { (HappyWrap143 happy_var_2) ->
4670	( ams (sLL happy_var_1 happy_var_2 (snd $ unLoc happy_var_2))
4671                                           (mj AnnForeign happy_var_1:(fst $ unLoc happy_var_2)))}})
4672	) (\r -> happyReturn (happyIn77 r))
4673
4674happyReduce_155 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4675happyReduce_155 = happyMonadReduce 3# 61# happyReduction_155
4676happyReduction_155 (happy_x_3 `HappyStk`
4677	happy_x_2 `HappyStk`
4678	happy_x_1 `HappyStk`
4679	happyRest) tk
4680	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4681	case happyOut138 happy_x_2 of { (HappyWrap138 happy_var_2) ->
4682	case happyOutTok happy_x_3 of { happy_var_3 ->
4683	( ams (sLL happy_var_1 happy_var_3 $ WarningD noExtField (Warnings noExtField (getDEPRECATED_PRAGs happy_var_1) (fromOL happy_var_2)))
4684                                                       [mo happy_var_1,mc happy_var_3])}}})
4685	) (\r -> happyReturn (happyIn77 r))
4686
4687happyReduce_156 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4688happyReduce_156 = happyMonadReduce 3# 61# happyReduction_156
4689happyReduction_156 (happy_x_3 `HappyStk`
4690	happy_x_2 `HappyStk`
4691	happy_x_1 `HappyStk`
4692	happyRest) tk
4693	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4694	case happyOut136 happy_x_2 of { (HappyWrap136 happy_var_2) ->
4695	case happyOutTok happy_x_3 of { happy_var_3 ->
4696	( ams (sLL happy_var_1 happy_var_3 $ WarningD noExtField (Warnings noExtField (getWARNING_PRAGs happy_var_1) (fromOL happy_var_2)))
4697                                                       [mo happy_var_1,mc happy_var_3])}}})
4698	) (\r -> happyReturn (happyIn77 r))
4699
4700happyReduce_157 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4701happyReduce_157 = happyMonadReduce 3# 61# happyReduction_157
4702happyReduction_157 (happy_x_3 `HappyStk`
4703	happy_x_2 `HappyStk`
4704	happy_x_1 `HappyStk`
4705	happyRest) tk
4706	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4707	case happyOut129 happy_x_2 of { (HappyWrap129 happy_var_2) ->
4708	case happyOutTok happy_x_3 of { happy_var_3 ->
4709	( ams (sLL happy_var_1 happy_var_3 $ RuleD noExtField (HsRules noExtField (getRULES_PRAGs happy_var_1) (fromOL happy_var_2)))
4710                                                       [mo happy_var_1,mc happy_var_3])}}})
4711	) (\r -> happyReturn (happyIn77 r))
4712
4713happyReduce_158 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4714happyReduce_158 = happySpecReduce_1  61# happyReduction_158
4715happyReduction_158 happy_x_1
4716	 =  case happyOut142 happy_x_1 of { (HappyWrap142 happy_var_1) ->
4717	happyIn77
4718		 (happy_var_1
4719	)}
4720
4721happyReduce_159 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4722happyReduce_159 = happySpecReduce_1  61# happyReduction_159
4723happyReduction_159 happy_x_1
4724	 =  case happyOut200 happy_x_1 of { (HappyWrap200 happy_var_1) ->
4725	happyIn77
4726		 (happy_var_1
4727	)}
4728
4729happyReduce_160 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4730happyReduce_160 = happyMonadReduce 1# 61# happyReduction_160
4731happyReduction_160 (happy_x_1 `HappyStk`
4732	happyRest) tk
4733	 = happyThen ((case happyOut211 happy_x_1 of { (HappyWrap211 happy_var_1) ->
4734	( runECP_P happy_var_1 >>= \ happy_var_1 ->
4735                                                   return $ sLL happy_var_1 happy_var_1 $ mkSpliceDecl happy_var_1)})
4736	) (\r -> happyReturn (happyIn77 r))
4737
4738happyReduce_161 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4739happyReduce_161 = happyMonadReduce 4# 62# happyReduction_161
4740happyReduction_161 (happy_x_4 `HappyStk`
4741	happy_x_3 `HappyStk`
4742	happy_x_2 `HappyStk`
4743	happy_x_1 `HappyStk`
4744	happyRest) tk
4745	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4746	case happyOut103 happy_x_2 of { (HappyWrap103 happy_var_2) ->
4747	case happyOut177 happy_x_3 of { (HappyWrap177 happy_var_3) ->
4748	case happyOut120 happy_x_4 of { (HappyWrap120 happy_var_4) ->
4749	( amms (mkClassDecl (comb4 happy_var_1 happy_var_2 happy_var_3 happy_var_4) happy_var_2 happy_var_3 (snd $ unLoc happy_var_4))
4750                        (mj AnnClass happy_var_1:(fst $ unLoc happy_var_3)++(fst $ unLoc happy_var_4)))}}}})
4751	) (\r -> happyReturn (happyIn78 r))
4752
4753happyReduce_162 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4754happyReduce_162 = happyMonadReduce 4# 63# happyReduction_162
4755happyReduction_162 (happy_x_4 `HappyStk`
4756	happy_x_3 `HappyStk`
4757	happy_x_2 `HappyStk`
4758	happy_x_1 `HappyStk`
4759	happyRest) tk
4760	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4761	case happyOut161 happy_x_2 of { (HappyWrap161 happy_var_2) ->
4762	case happyOutTok happy_x_3 of { happy_var_3 ->
4763	case happyOut156 happy_x_4 of { (HappyWrap156 happy_var_4) ->
4764	( amms (mkTySynonym (comb2 happy_var_1 happy_var_4) happy_var_2 happy_var_4)
4765                        [mj AnnType happy_var_1,mj AnnEqual happy_var_3])}}}})
4766	) (\r -> happyReturn (happyIn79 r))
4767
4768happyReduce_163 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4769happyReduce_163 = happyMonadReduce 6# 63# happyReduction_163
4770happyReduction_163 (happy_x_6 `HappyStk`
4771	happy_x_5 `HappyStk`
4772	happy_x_4 `HappyStk`
4773	happy_x_3 `HappyStk`
4774	happy_x_2 `HappyStk`
4775	happy_x_1 `HappyStk`
4776	happyRest) tk
4777	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4778	case happyOutTok happy_x_2 of { happy_var_2 ->
4779	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
4780	case happyOut101 happy_x_4 of { (HappyWrap101 happy_var_4) ->
4781	case happyOut87 happy_x_5 of { (HappyWrap87 happy_var_5) ->
4782	case happyOut90 happy_x_6 of { (HappyWrap90 happy_var_6) ->
4783	( amms (mkFamDecl (comb4 happy_var_1 happy_var_3 happy_var_4 happy_var_5) (snd $ unLoc happy_var_6) happy_var_3
4784                                   (snd $ unLoc happy_var_4) (snd $ unLoc happy_var_5))
4785                        (mj AnnType happy_var_1:mj AnnFamily happy_var_2:(fst $ unLoc happy_var_4)
4786                           ++ (fst $ unLoc happy_var_5) ++ (fst $ unLoc happy_var_6)))}}}}}})
4787	) (\r -> happyReturn (happyIn79 r))
4788
4789happyReduce_164 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4790happyReduce_164 = happyMonadReduce 5# 63# happyReduction_164
4791happyReduction_164 (happy_x_5 `HappyStk`
4792	happy_x_4 `HappyStk`
4793	happy_x_3 `HappyStk`
4794	happy_x_2 `HappyStk`
4795	happy_x_1 `HappyStk`
4796	happyRest) tk
4797	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
4798	case happyOut105 happy_x_2 of { (HappyWrap105 happy_var_2) ->
4799	case happyOut103 happy_x_3 of { (HappyWrap103 happy_var_3) ->
4800	case happyOut186 happy_x_4 of { (HappyWrap186 happy_var_4) ->
4801	case happyOut194 happy_x_5 of { (HappyWrap194 happy_var_5) ->
4802	( amms (mkTyData (comb4 happy_var_1 happy_var_3 happy_var_4 happy_var_5) (snd $ unLoc happy_var_1) happy_var_2 happy_var_3
4803                           Nothing (reverse (snd $ unLoc happy_var_4))
4804                                   (fmap reverse happy_var_5))
4805                                   -- We need the location on tycl_hdr in case
4806                                   -- constrs and deriving are both empty
4807                        ((fst $ unLoc happy_var_1):(fst $ unLoc happy_var_4)))}}}}})
4808	) (\r -> happyReturn (happyIn79 r))
4809
4810happyReduce_165 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4811happyReduce_165 = happyMonadReduce 6# 63# happyReduction_165
4812happyReduction_165 (happy_x_6 `HappyStk`
4813	happy_x_5 `HappyStk`
4814	happy_x_4 `HappyStk`
4815	happy_x_3 `HappyStk`
4816	happy_x_2 `HappyStk`
4817	happy_x_1 `HappyStk`
4818	happyRest) tk
4819	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
4820	case happyOut105 happy_x_2 of { (HappyWrap105 happy_var_2) ->
4821	case happyOut103 happy_x_3 of { (HappyWrap103 happy_var_3) ->
4822	case happyOut99 happy_x_4 of { (HappyWrap99 happy_var_4) ->
4823	case happyOut182 happy_x_5 of { (HappyWrap182 happy_var_5) ->
4824	case happyOut194 happy_x_6 of { (HappyWrap194 happy_var_6) ->
4825	( amms (mkTyData (comb4 happy_var_1 happy_var_3 happy_var_5 happy_var_6) (snd $ unLoc happy_var_1) happy_var_2 happy_var_3
4826                            (snd $ unLoc happy_var_4) (snd $ unLoc happy_var_5)
4827                            (fmap reverse happy_var_6) )
4828                                   -- We need the location on tycl_hdr in case
4829                                   -- constrs and deriving are both empty
4830                    ((fst $ unLoc happy_var_1):(fst $ unLoc happy_var_4)++(fst $ unLoc happy_var_5)))}}}}}})
4831	) (\r -> happyReturn (happyIn79 r))
4832
4833happyReduce_166 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4834happyReduce_166 = happyMonadReduce 4# 63# happyReduction_166
4835happyReduction_166 (happy_x_4 `HappyStk`
4836	happy_x_3 `HappyStk`
4837	happy_x_2 `HappyStk`
4838	happy_x_1 `HappyStk`
4839	happyRest) tk
4840	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4841	case happyOutTok happy_x_2 of { happy_var_2 ->
4842	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
4843	case happyOut100 happy_x_4 of { (HappyWrap100 happy_var_4) ->
4844	( amms (mkFamDecl (comb3 happy_var_1 happy_var_2 happy_var_4) DataFamily happy_var_3
4845                                   (snd $ unLoc happy_var_4) Nothing)
4846                        (mj AnnData happy_var_1:mj AnnFamily happy_var_2:(fst $ unLoc happy_var_4)))}}}})
4847	) (\r -> happyReturn (happyIn79 r))
4848
4849happyReduce_167 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4850happyReduce_167 = happyMonadReduce 4# 64# happyReduction_167
4851happyReduction_167 (happy_x_4 `HappyStk`
4852	happy_x_3 `HappyStk`
4853	happy_x_2 `HappyStk`
4854	happy_x_1 `HappyStk`
4855	happyRest) tk
4856	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4857	case happyOut81 happy_x_2 of { (HappyWrap81 happy_var_2) ->
4858	case happyOutTok happy_x_3 of { happy_var_3 ->
4859	case happyOut156 happy_x_4 of { (HappyWrap156 happy_var_4) ->
4860	( amms (mkStandaloneKindSig (comb2 happy_var_1 happy_var_4) happy_var_2 happy_var_4)
4861              [mj AnnType happy_var_1,mu AnnDcolon happy_var_3])}}}})
4862	) (\r -> happyReturn (happyIn80 r))
4863
4864happyReduce_168 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4865happyReduce_168 = happyMonadReduce 3# 65# happyReduction_168
4866happyReduction_168 (happy_x_3 `HappyStk`
4867	happy_x_2 `HappyStk`
4868	happy_x_1 `HappyStk`
4869	happyRest) tk
4870	 = happyThen ((case happyOut81 happy_x_1 of { (HappyWrap81 happy_var_1) ->
4871	case happyOutTok happy_x_2 of { happy_var_2 ->
4872	case happyOut284 happy_x_3 of { (HappyWrap284 happy_var_3) ->
4873	( addAnnotation (gl $ head $ unLoc happy_var_1) AnnComma (gl happy_var_2) >>
4874         return (sLL happy_var_1 happy_var_3 (happy_var_3 : unLoc happy_var_1)))}}})
4875	) (\r -> happyReturn (happyIn81 r))
4876
4877happyReduce_169 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4878happyReduce_169 = happySpecReduce_1  65# happyReduction_169
4879happyReduction_169 happy_x_1
4880	 =  case happyOut284 happy_x_1 of { (HappyWrap284 happy_var_1) ->
4881	happyIn81
4882		 (sL1 happy_var_1 [happy_var_1]
4883	)}
4884
4885happyReduce_170 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4886happyReduce_170 = happyMonadReduce 4# 66# happyReduction_170
4887happyReduction_170 (happy_x_4 `HappyStk`
4888	happy_x_3 `HappyStk`
4889	happy_x_2 `HappyStk`
4890	happy_x_1 `HappyStk`
4891	happyRest) tk
4892	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4893	case happyOut83 happy_x_2 of { (HappyWrap83 happy_var_2) ->
4894	case happyOut170 happy_x_3 of { (HappyWrap170 happy_var_3) ->
4895	case happyOut124 happy_x_4 of { (HappyWrap124 happy_var_4) ->
4896	( do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (snd $ unLoc happy_var_4)
4897             ; let cid = ClsInstDecl { cid_ext = noExtField
4898                                     , cid_poly_ty = happy_var_3, cid_binds = binds
4899                                     , cid_sigs = mkClassOpSigs sigs
4900                                     , cid_tyfam_insts = ats
4901                                     , cid_overlap_mode = happy_var_2
4902                                     , cid_datafam_insts = adts }
4903             ; ams (cL (comb3 happy_var_1 (hsSigType happy_var_3) happy_var_4) (ClsInstD { cid_d_ext = noExtField, cid_inst = cid }))
4904                   (mj AnnInstance happy_var_1 : (fst $ unLoc happy_var_4)) })}}}})
4905	) (\r -> happyReturn (happyIn82 r))
4906
4907happyReduce_171 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4908happyReduce_171 = happyMonadReduce 3# 66# happyReduction_171
4909happyReduction_171 (happy_x_3 `HappyStk`
4910	happy_x_2 `HappyStk`
4911	happy_x_1 `HappyStk`
4912	happyRest) tk
4913	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4914	case happyOutTok happy_x_2 of { happy_var_2 ->
4915	case happyOut93 happy_x_3 of { (HappyWrap93 happy_var_3) ->
4916	( ams happy_var_3 (fst $ unLoc happy_var_3)
4917                >> amms (mkTyFamInst (comb2 happy_var_1 happy_var_3) (snd $ unLoc happy_var_3))
4918                    (mj AnnType happy_var_1:mj AnnInstance happy_var_2:(fst $ unLoc happy_var_3)))}}})
4919	) (\r -> happyReturn (happyIn82 r))
4920
4921happyReduce_172 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4922happyReduce_172 = happyMonadReduce 6# 66# happyReduction_172
4923happyReduction_172 (happy_x_6 `HappyStk`
4924	happy_x_5 `HappyStk`
4925	happy_x_4 `HappyStk`
4926	happy_x_3 `HappyStk`
4927	happy_x_2 `HappyStk`
4928	happy_x_1 `HappyStk`
4929	happyRest) tk
4930	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
4931	case happyOutTok happy_x_2 of { happy_var_2 ->
4932	case happyOut105 happy_x_3 of { (HappyWrap105 happy_var_3) ->
4933	case happyOut104 happy_x_4 of { (HappyWrap104 happy_var_4) ->
4934	case happyOut186 happy_x_5 of { (HappyWrap186 happy_var_5) ->
4935	case happyOut194 happy_x_6 of { (HappyWrap194 happy_var_6) ->
4936	( amms (mkDataFamInst (comb4 happy_var_1 happy_var_4 happy_var_5 happy_var_6) (snd $ unLoc happy_var_1) happy_var_3 (snd $ unLoc happy_var_4)
4937                                      Nothing (reverse (snd  $ unLoc happy_var_5))
4938                                              (fmap reverse happy_var_6))
4939                    ((fst $ unLoc happy_var_1):mj AnnInstance happy_var_2:(fst $ unLoc happy_var_4)++(fst $ unLoc happy_var_5)))}}}}}})
4940	) (\r -> happyReturn (happyIn82 r))
4941
4942happyReduce_173 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4943happyReduce_173 = happyMonadReduce 7# 66# happyReduction_173
4944happyReduction_173 (happy_x_7 `HappyStk`
4945	happy_x_6 `HappyStk`
4946	happy_x_5 `HappyStk`
4947	happy_x_4 `HappyStk`
4948	happy_x_3 `HappyStk`
4949	happy_x_2 `HappyStk`
4950	happy_x_1 `HappyStk`
4951	happyRest) tk
4952	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
4953	case happyOutTok happy_x_2 of { happy_var_2 ->
4954	case happyOut105 happy_x_3 of { (HappyWrap105 happy_var_3) ->
4955	case happyOut104 happy_x_4 of { (HappyWrap104 happy_var_4) ->
4956	case happyOut99 happy_x_5 of { (HappyWrap99 happy_var_5) ->
4957	case happyOut182 happy_x_6 of { (HappyWrap182 happy_var_6) ->
4958	case happyOut194 happy_x_7 of { (HappyWrap194 happy_var_7) ->
4959	( amms (mkDataFamInst (comb4 happy_var_1 happy_var_4 happy_var_6 happy_var_7) (snd $ unLoc happy_var_1) happy_var_3 (snd $ unLoc happy_var_4)
4960                                   (snd $ unLoc happy_var_5) (snd $ unLoc happy_var_6)
4961                                   (fmap reverse happy_var_7))
4962                    ((fst $ unLoc happy_var_1):mj AnnInstance happy_var_2
4963                       :(fst $ unLoc happy_var_4)++(fst $ unLoc happy_var_5)++(fst $ unLoc happy_var_6)))}}}}}}})
4964	) (\r -> happyReturn (happyIn82 r))
4965
4966happyReduce_174 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4967happyReduce_174 = happyMonadReduce 2# 67# happyReduction_174
4968happyReduction_174 (happy_x_2 `HappyStk`
4969	happy_x_1 `HappyStk`
4970	happyRest) tk
4971	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4972	case happyOutTok happy_x_2 of { happy_var_2 ->
4973	( ajs (sLL happy_var_1 happy_var_2 (Overlappable (getOVERLAPPABLE_PRAGs happy_var_1)))
4974                                       [mo happy_var_1,mc happy_var_2])}})
4975	) (\r -> happyReturn (happyIn83 r))
4976
4977happyReduce_175 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4978happyReduce_175 = happyMonadReduce 2# 67# happyReduction_175
4979happyReduction_175 (happy_x_2 `HappyStk`
4980	happy_x_1 `HappyStk`
4981	happyRest) tk
4982	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4983	case happyOutTok happy_x_2 of { happy_var_2 ->
4984	( ajs (sLL happy_var_1 happy_var_2 (Overlapping (getOVERLAPPING_PRAGs happy_var_1)))
4985                                       [mo happy_var_1,mc happy_var_2])}})
4986	) (\r -> happyReturn (happyIn83 r))
4987
4988happyReduce_176 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
4989happyReduce_176 = happyMonadReduce 2# 67# happyReduction_176
4990happyReduction_176 (happy_x_2 `HappyStk`
4991	happy_x_1 `HappyStk`
4992	happyRest) tk
4993	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
4994	case happyOutTok happy_x_2 of { happy_var_2 ->
4995	( ajs (sLL happy_var_1 happy_var_2 (Overlaps (getOVERLAPS_PRAGs happy_var_1)))
4996                                       [mo happy_var_1,mc happy_var_2])}})
4997	) (\r -> happyReturn (happyIn83 r))
4998
4999happyReduce_177 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5000happyReduce_177 = happyMonadReduce 2# 67# happyReduction_177
5001happyReduction_177 (happy_x_2 `HappyStk`
5002	happy_x_1 `HappyStk`
5003	happyRest) tk
5004	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5005	case happyOutTok happy_x_2 of { happy_var_2 ->
5006	( ajs (sLL happy_var_1 happy_var_2 (Incoherent (getINCOHERENT_PRAGs happy_var_1)))
5007                                       [mo happy_var_1,mc happy_var_2])}})
5008	) (\r -> happyReturn (happyIn83 r))
5009
5010happyReduce_178 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5011happyReduce_178 = happySpecReduce_0  67# happyReduction_178
5012happyReduction_178  =  happyIn83
5013		 (Nothing
5014	)
5015
5016happyReduce_179 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5017happyReduce_179 = happyMonadReduce 1# 68# happyReduction_179
5018happyReduction_179 (happy_x_1 `HappyStk`
5019	happyRest) tk
5020	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5021	( ams (sL1 happy_var_1 StockStrategy)
5022                                       [mj AnnStock happy_var_1])})
5023	) (\r -> happyReturn (happyIn84 r))
5024
5025happyReduce_180 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5026happyReduce_180 = happyMonadReduce 1# 68# happyReduction_180
5027happyReduction_180 (happy_x_1 `HappyStk`
5028	happyRest) tk
5029	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5030	( ams (sL1 happy_var_1 AnyclassStrategy)
5031                                       [mj AnnAnyclass happy_var_1])})
5032	) (\r -> happyReturn (happyIn84 r))
5033
5034happyReduce_181 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5035happyReduce_181 = happyMonadReduce 1# 68# happyReduction_181
5036happyReduction_181 (happy_x_1 `HappyStk`
5037	happyRest) tk
5038	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5039	( ams (sL1 happy_var_1 NewtypeStrategy)
5040                                       [mj AnnNewtype happy_var_1])})
5041	) (\r -> happyReturn (happyIn84 r))
5042
5043happyReduce_182 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5044happyReduce_182 = happyMonadReduce 2# 69# happyReduction_182
5045happyReduction_182 (happy_x_2 `HappyStk`
5046	happy_x_1 `HappyStk`
5047	happyRest) tk
5048	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5049	case happyOut161 happy_x_2 of { (HappyWrap161 happy_var_2) ->
5050	( ams (sLL happy_var_1 happy_var_2 (ViaStrategy (mkLHsSigType happy_var_2)))
5051                                            [mj AnnVia happy_var_1])}})
5052	) (\r -> happyReturn (happyIn85 r))
5053
5054happyReduce_183 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5055happyReduce_183 = happyMonadReduce 1# 70# happyReduction_183
5056happyReduction_183 (happy_x_1 `HappyStk`
5057	happyRest) tk
5058	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5059	( ajs (sL1 happy_var_1 StockStrategy)
5060                                       [mj AnnStock happy_var_1])})
5061	) (\r -> happyReturn (happyIn86 r))
5062
5063happyReduce_184 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5064happyReduce_184 = happyMonadReduce 1# 70# happyReduction_184
5065happyReduction_184 (happy_x_1 `HappyStk`
5066	happyRest) tk
5067	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5068	( ajs (sL1 happy_var_1 AnyclassStrategy)
5069                                       [mj AnnAnyclass happy_var_1])})
5070	) (\r -> happyReturn (happyIn86 r))
5071
5072happyReduce_185 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5073happyReduce_185 = happyMonadReduce 1# 70# happyReduction_185
5074happyReduction_185 (happy_x_1 `HappyStk`
5075	happyRest) tk
5076	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5077	( ajs (sL1 happy_var_1 NewtypeStrategy)
5078                                       [mj AnnNewtype happy_var_1])})
5079	) (\r -> happyReturn (happyIn86 r))
5080
5081happyReduce_186 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5082happyReduce_186 = happySpecReduce_1  70# happyReduction_186
5083happyReduction_186 happy_x_1
5084	 =  case happyOut85 happy_x_1 of { (HappyWrap85 happy_var_1) ->
5085	happyIn86
5086		 (Just happy_var_1
5087	)}
5088
5089happyReduce_187 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5090happyReduce_187 = happySpecReduce_0  70# happyReduction_187
5091happyReduction_187  =  happyIn86
5092		 (Nothing
5093	)
5094
5095happyReduce_188 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5096happyReduce_188 = happySpecReduce_0  71# happyReduction_188
5097happyReduction_188  =  happyIn87
5098		 (noLoc ([], Nothing)
5099	)
5100
5101happyReduce_189 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5102happyReduce_189 = happySpecReduce_2  71# happyReduction_189
5103happyReduction_189 happy_x_2
5104	happy_x_1
5105	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5106	case happyOut88 happy_x_2 of { (HappyWrap88 happy_var_2) ->
5107	happyIn87
5108		 (sLL happy_var_1 happy_var_2 ([mj AnnVbar happy_var_1]
5109                                                , Just (happy_var_2))
5110	)}}
5111
5112happyReduce_190 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5113happyReduce_190 = happyMonadReduce 3# 72# happyReduction_190
5114happyReduction_190 (happy_x_3 `HappyStk`
5115	happy_x_2 `HappyStk`
5116	happy_x_1 `HappyStk`
5117	happyRest) tk
5118	 = happyThen ((case happyOut301 happy_x_1 of { (HappyWrap301 happy_var_1) ->
5119	case happyOutTok happy_x_2 of { happy_var_2 ->
5120	case happyOut89 happy_x_3 of { (HappyWrap89 happy_var_3) ->
5121	( ams (sLL happy_var_1 happy_var_3 (InjectivityAnn happy_var_1 (reverse (unLoc happy_var_3))))
5122                  [mu AnnRarrow happy_var_2])}}})
5123	) (\r -> happyReturn (happyIn88 r))
5124
5125happyReduce_191 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5126happyReduce_191 = happySpecReduce_2  73# happyReduction_191
5127happyReduction_191 happy_x_2
5128	happy_x_1
5129	 =  case happyOut89 happy_x_1 of { (HappyWrap89 happy_var_1) ->
5130	case happyOut301 happy_x_2 of { (HappyWrap301 happy_var_2) ->
5131	happyIn89
5132		 (sLL happy_var_1 happy_var_2 (happy_var_2 : unLoc happy_var_1)
5133	)}}
5134
5135happyReduce_192 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5136happyReduce_192 = happySpecReduce_1  73# happyReduction_192
5137happyReduction_192 happy_x_1
5138	 =  case happyOut301 happy_x_1 of { (HappyWrap301 happy_var_1) ->
5139	happyIn89
5140		 (sLL happy_var_1 happy_var_1 [happy_var_1]
5141	)}
5142
5143happyReduce_193 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5144happyReduce_193 = happySpecReduce_0  74# happyReduction_193
5145happyReduction_193  =  happyIn90
5146		 (noLoc ([],OpenTypeFamily)
5147	)
5148
5149happyReduce_194 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5150happyReduce_194 = happySpecReduce_2  74# happyReduction_194
5151happyReduction_194 happy_x_2
5152	happy_x_1
5153	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5154	case happyOut91 happy_x_2 of { (HappyWrap91 happy_var_2) ->
5155	happyIn90
5156		 (sLL happy_var_1 happy_var_2 (mj AnnWhere happy_var_1:(fst $ unLoc happy_var_2)
5157                    ,ClosedTypeFamily (fmap reverse $ snd $ unLoc happy_var_2))
5158	)}}
5159
5160happyReduce_195 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5161happyReduce_195 = happySpecReduce_3  75# happyReduction_195
5162happyReduction_195 happy_x_3
5163	happy_x_2
5164	happy_x_1
5165	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5166	case happyOut92 happy_x_2 of { (HappyWrap92 happy_var_2) ->
5167	case happyOutTok happy_x_3 of { happy_var_3 ->
5168	happyIn91
5169		 (sLL happy_var_1 happy_var_3 ([moc happy_var_1,mcc happy_var_3]
5170                                                ,Just (unLoc happy_var_2))
5171	)}}}
5172
5173happyReduce_196 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5174happyReduce_196 = happySpecReduce_3  75# happyReduction_196
5175happyReduction_196 happy_x_3
5176	happy_x_2
5177	happy_x_1
5178	 =  case happyOut92 happy_x_2 of { (HappyWrap92 happy_var_2) ->
5179	happyIn91
5180		 (let (dL->L loc _) = happy_var_2 in
5181                                             cL loc ([],Just (unLoc happy_var_2))
5182	)}
5183
5184happyReduce_197 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5185happyReduce_197 = happySpecReduce_3  75# happyReduction_197
5186happyReduction_197 happy_x_3
5187	happy_x_2
5188	happy_x_1
5189	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5190	case happyOutTok happy_x_2 of { happy_var_2 ->
5191	case happyOutTok happy_x_3 of { happy_var_3 ->
5192	happyIn91
5193		 (sLL happy_var_1 happy_var_3 ([moc happy_var_1,mj AnnDotdot happy_var_2
5194                                                 ,mcc happy_var_3],Nothing)
5195	)}}}
5196
5197happyReduce_198 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5198happyReduce_198 = happySpecReduce_3  75# happyReduction_198
5199happyReduction_198 happy_x_3
5200	happy_x_2
5201	happy_x_1
5202	 =  case happyOutTok happy_x_2 of { happy_var_2 ->
5203	happyIn91
5204		 (let (dL->L loc _) = happy_var_2 in
5205                                             cL loc ([mj AnnDotdot happy_var_2],Nothing)
5206	)}
5207
5208happyReduce_199 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5209happyReduce_199 = happyMonadReduce 3# 76# happyReduction_199
5210happyReduction_199 (happy_x_3 `HappyStk`
5211	happy_x_2 `HappyStk`
5212	happy_x_1 `HappyStk`
5213	happyRest) tk
5214	 = happyThen ((case happyOut92 happy_x_1 of { (HappyWrap92 happy_var_1) ->
5215	case happyOutTok happy_x_2 of { happy_var_2 ->
5216	case happyOut93 happy_x_3 of { (HappyWrap93 happy_var_3) ->
5217	( let (dL->L loc (anns, eqn)) = happy_var_3 in
5218                                         asl (unLoc happy_var_1) happy_var_2 (cL loc eqn)
5219                                         >> ams happy_var_3 anns
5220                                         >> return (sLL happy_var_1 happy_var_3 (cL loc eqn : unLoc happy_var_1)))}}})
5221	) (\r -> happyReturn (happyIn92 r))
5222
5223happyReduce_200 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5224happyReduce_200 = happyMonadReduce 2# 76# happyReduction_200
5225happyReduction_200 (happy_x_2 `HappyStk`
5226	happy_x_1 `HappyStk`
5227	happyRest) tk
5228	 = happyThen ((case happyOut92 happy_x_1 of { (HappyWrap92 happy_var_1) ->
5229	case happyOutTok happy_x_2 of { happy_var_2 ->
5230	( addAnnotation (gl happy_var_1) AnnSemi (gl happy_var_2)
5231                                         >> return (sLL happy_var_1 happy_var_2  (unLoc happy_var_1)))}})
5232	) (\r -> happyReturn (happyIn92 r))
5233
5234happyReduce_201 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5235happyReduce_201 = happyMonadReduce 1# 76# happyReduction_201
5236happyReduction_201 (happy_x_1 `HappyStk`
5237	happyRest) tk
5238	 = happyThen ((case happyOut93 happy_x_1 of { (HappyWrap93 happy_var_1) ->
5239	( let (dL->L loc (anns, eqn)) = happy_var_1 in
5240                                         ams happy_var_1 anns
5241                                         >> return (sLL happy_var_1 happy_var_1 [cL loc eqn]))})
5242	) (\r -> happyReturn (happyIn92 r))
5243
5244happyReduce_202 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5245happyReduce_202 = happySpecReduce_0  76# happyReduction_202
5246happyReduction_202  =  happyIn92
5247		 (noLoc []
5248	)
5249
5250happyReduce_203 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5251happyReduce_203 = happyMonadReduce 6# 77# happyReduction_203
5252happyReduction_203 (happy_x_6 `HappyStk`
5253	happy_x_5 `HappyStk`
5254	happy_x_4 `HappyStk`
5255	happy_x_3 `HappyStk`
5256	happy_x_2 `HappyStk`
5257	happy_x_1 `HappyStk`
5258	happyRest) tk
5259	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5260	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
5261	case happyOutTok happy_x_3 of { happy_var_3 ->
5262	case happyOut161 happy_x_4 of { (HappyWrap161 happy_var_4) ->
5263	case happyOutTok happy_x_5 of { happy_var_5 ->
5264	case happyOut155 happy_x_6 of { (HappyWrap155 happy_var_6) ->
5265	( do { hintExplicitForall happy_var_1
5266                    ; (eqn,ann) <- mkTyFamInstEqn (Just happy_var_2) happy_var_4 happy_var_6
5267                    ; return (sLL happy_var_1 happy_var_6
5268                               (mu AnnForall happy_var_1:mj AnnDot happy_var_3:mj AnnEqual happy_var_5:ann,eqn)) })}}}}}})
5269	) (\r -> happyReturn (happyIn93 r))
5270
5271happyReduce_204 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5272happyReduce_204 = happyMonadReduce 3# 77# happyReduction_204
5273happyReduction_204 (happy_x_3 `HappyStk`
5274	happy_x_2 `HappyStk`
5275	happy_x_1 `HappyStk`
5276	happyRest) tk
5277	 = happyThen ((case happyOut161 happy_x_1 of { (HappyWrap161 happy_var_1) ->
5278	case happyOutTok happy_x_2 of { happy_var_2 ->
5279	case happyOut155 happy_x_3 of { (HappyWrap155 happy_var_3) ->
5280	( do { (eqn,ann) <- mkTyFamInstEqn Nothing happy_var_1 happy_var_3
5281                    ; return (sLL happy_var_1 happy_var_3 (mj AnnEqual happy_var_2:ann, eqn))  })}}})
5282	) (\r -> happyReturn (happyIn93 r))
5283
5284happyReduce_205 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5285happyReduce_205 = happyMonadReduce 4# 78# happyReduction_205
5286happyReduction_205 (happy_x_4 `HappyStk`
5287	happy_x_3 `HappyStk`
5288	happy_x_2 `HappyStk`
5289	happy_x_1 `HappyStk`
5290	happyRest) tk
5291	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5292	case happyOut95 happy_x_2 of { (HappyWrap95 happy_var_2) ->
5293	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
5294	case happyOut100 happy_x_4 of { (HappyWrap100 happy_var_4) ->
5295	( amms (liftM mkTyClD (mkFamDecl (comb3 happy_var_1 happy_var_3 happy_var_4) DataFamily happy_var_3
5296                                                  (snd $ unLoc happy_var_4) Nothing))
5297                        (mj AnnData happy_var_1:happy_var_2++(fst $ unLoc happy_var_4)))}}}})
5298	) (\r -> happyReturn (happyIn94 r))
5299
5300happyReduce_206 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5301happyReduce_206 = happyMonadReduce 3# 78# happyReduction_206
5302happyReduction_206 (happy_x_3 `HappyStk`
5303	happy_x_2 `HappyStk`
5304	happy_x_1 `HappyStk`
5305	happyRest) tk
5306	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5307	case happyOut161 happy_x_2 of { (HappyWrap161 happy_var_2) ->
5308	case happyOut102 happy_x_3 of { (HappyWrap102 happy_var_3) ->
5309	( amms (liftM mkTyClD
5310                        (mkFamDecl (comb3 happy_var_1 happy_var_2 happy_var_3) OpenTypeFamily happy_var_2
5311                                   (fst . snd $ unLoc happy_var_3)
5312                                   (snd . snd $ unLoc happy_var_3)))
5313                       (mj AnnType happy_var_1:(fst $ unLoc happy_var_3)))}}})
5314	) (\r -> happyReturn (happyIn94 r))
5315
5316happyReduce_207 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5317happyReduce_207 = happyMonadReduce 4# 78# happyReduction_207
5318happyReduction_207 (happy_x_4 `HappyStk`
5319	happy_x_3 `HappyStk`
5320	happy_x_2 `HappyStk`
5321	happy_x_1 `HappyStk`
5322	happyRest) tk
5323	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5324	case happyOutTok happy_x_2 of { happy_var_2 ->
5325	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
5326	case happyOut102 happy_x_4 of { (HappyWrap102 happy_var_4) ->
5327	( amms (liftM mkTyClD
5328                        (mkFamDecl (comb3 happy_var_1 happy_var_3 happy_var_4) OpenTypeFamily happy_var_3
5329                                   (fst . snd $ unLoc happy_var_4)
5330                                   (snd . snd $ unLoc happy_var_4)))
5331                       (mj AnnType happy_var_1:mj AnnFamily happy_var_2:(fst $ unLoc happy_var_4)))}}}})
5332	) (\r -> happyReturn (happyIn94 r))
5333
5334happyReduce_208 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5335happyReduce_208 = happyMonadReduce 2# 78# happyReduction_208
5336happyReduction_208 (happy_x_2 `HappyStk`
5337	happy_x_1 `HappyStk`
5338	happyRest) tk
5339	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5340	case happyOut93 happy_x_2 of { (HappyWrap93 happy_var_2) ->
5341	( ams happy_var_2 (fst $ unLoc happy_var_2) >>
5342                   amms (liftM mkInstD (mkTyFamInst (comb2 happy_var_1 happy_var_2) (snd $ unLoc happy_var_2)))
5343                        (mj AnnType happy_var_1:(fst $ unLoc happy_var_2)))}})
5344	) (\r -> happyReturn (happyIn94 r))
5345
5346happyReduce_209 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5347happyReduce_209 = happyMonadReduce 3# 78# happyReduction_209
5348happyReduction_209 (happy_x_3 `HappyStk`
5349	happy_x_2 `HappyStk`
5350	happy_x_1 `HappyStk`
5351	happyRest) tk
5352	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5353	case happyOutTok happy_x_2 of { happy_var_2 ->
5354	case happyOut93 happy_x_3 of { (HappyWrap93 happy_var_3) ->
5355	( ams happy_var_3 (fst $ unLoc happy_var_3) >>
5356                   amms (liftM mkInstD (mkTyFamInst (comb2 happy_var_1 happy_var_3) (snd $ unLoc happy_var_3)))
5357                        (mj AnnType happy_var_1:mj AnnInstance happy_var_2:(fst $ unLoc happy_var_3)))}}})
5358	) (\r -> happyReturn (happyIn94 r))
5359
5360happyReduce_210 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5361happyReduce_210 = happySpecReduce_0  79# happyReduction_210
5362happyReduction_210  =  happyIn95
5363		 ([]
5364	)
5365
5366happyReduce_211 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5367happyReduce_211 = happySpecReduce_1  79# happyReduction_211
5368happyReduction_211 happy_x_1
5369	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5370	happyIn95
5371		 ([mj AnnFamily happy_var_1]
5372	)}
5373
5374happyReduce_212 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5375happyReduce_212 = happySpecReduce_0  80# happyReduction_212
5376happyReduction_212  =  happyIn96
5377		 ([]
5378	)
5379
5380happyReduce_213 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5381happyReduce_213 = happySpecReduce_1  80# happyReduction_213
5382happyReduction_213 happy_x_1
5383	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5384	happyIn96
5385		 ([mj AnnInstance happy_var_1]
5386	)}
5387
5388happyReduce_214 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5389happyReduce_214 = happyMonadReduce 3# 81# happyReduction_214
5390happyReduction_214 (happy_x_3 `HappyStk`
5391	happy_x_2 `HappyStk`
5392	happy_x_1 `HappyStk`
5393	happyRest) tk
5394	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5395	case happyOut96 happy_x_2 of { (HappyWrap96 happy_var_2) ->
5396	case happyOut93 happy_x_3 of { (HappyWrap93 happy_var_3) ->
5397	( ams happy_var_3 (fst $ unLoc happy_var_3) >>
5398                   amms (mkTyFamInst (comb2 happy_var_1 happy_var_3) (snd $ unLoc happy_var_3))
5399                        (mj AnnType happy_var_1:happy_var_2++(fst $ unLoc happy_var_3)))}}})
5400	) (\r -> happyReturn (happyIn97 r))
5401
5402happyReduce_215 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5403happyReduce_215 = happyMonadReduce 6# 81# happyReduction_215
5404happyReduction_215 (happy_x_6 `HappyStk`
5405	happy_x_5 `HappyStk`
5406	happy_x_4 `HappyStk`
5407	happy_x_3 `HappyStk`
5408	happy_x_2 `HappyStk`
5409	happy_x_1 `HappyStk`
5410	happyRest) tk
5411	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
5412	case happyOut96 happy_x_2 of { (HappyWrap96 happy_var_2) ->
5413	case happyOut105 happy_x_3 of { (HappyWrap105 happy_var_3) ->
5414	case happyOut104 happy_x_4 of { (HappyWrap104 happy_var_4) ->
5415	case happyOut186 happy_x_5 of { (HappyWrap186 happy_var_5) ->
5416	case happyOut194 happy_x_6 of { (HappyWrap194 happy_var_6) ->
5417	( amms (mkDataFamInst (comb4 happy_var_1 happy_var_4 happy_var_5 happy_var_6) (snd $ unLoc happy_var_1) happy_var_3 (snd $ unLoc happy_var_4)
5418                                    Nothing (reverse (snd $ unLoc happy_var_5))
5419                                            (fmap reverse happy_var_6))
5420                       ((fst $ unLoc happy_var_1):happy_var_2++(fst $ unLoc happy_var_4)++(fst $ unLoc happy_var_5)))}}}}}})
5421	) (\r -> happyReturn (happyIn97 r))
5422
5423happyReduce_216 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5424happyReduce_216 = happyMonadReduce 7# 81# happyReduction_216
5425happyReduction_216 (happy_x_7 `HappyStk`
5426	happy_x_6 `HappyStk`
5427	happy_x_5 `HappyStk`
5428	happy_x_4 `HappyStk`
5429	happy_x_3 `HappyStk`
5430	happy_x_2 `HappyStk`
5431	happy_x_1 `HappyStk`
5432	happyRest) tk
5433	 = happyThen ((case happyOut98 happy_x_1 of { (HappyWrap98 happy_var_1) ->
5434	case happyOut96 happy_x_2 of { (HappyWrap96 happy_var_2) ->
5435	case happyOut105 happy_x_3 of { (HappyWrap105 happy_var_3) ->
5436	case happyOut104 happy_x_4 of { (HappyWrap104 happy_var_4) ->
5437	case happyOut99 happy_x_5 of { (HappyWrap99 happy_var_5) ->
5438	case happyOut182 happy_x_6 of { (HappyWrap182 happy_var_6) ->
5439	case happyOut194 happy_x_7 of { (HappyWrap194 happy_var_7) ->
5440	( amms (mkDataFamInst (comb4 happy_var_1 happy_var_4 happy_var_6 happy_var_7) (snd $ unLoc happy_var_1) happy_var_3
5441                                (snd $ unLoc happy_var_4) (snd $ unLoc happy_var_5) (snd $ unLoc happy_var_6)
5442                                (fmap reverse happy_var_7))
5443                        ((fst $ unLoc happy_var_1):happy_var_2++(fst $ unLoc happy_var_4)++(fst $ unLoc happy_var_5)++(fst $ unLoc happy_var_6)))}}}}}}})
5444	) (\r -> happyReturn (happyIn97 r))
5445
5446happyReduce_217 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5447happyReduce_217 = happySpecReduce_1  82# happyReduction_217
5448happyReduction_217 happy_x_1
5449	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5450	happyIn98
5451		 (sL1 happy_var_1 (mj AnnData    happy_var_1,DataType)
5452	)}
5453
5454happyReduce_218 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5455happyReduce_218 = happySpecReduce_1  82# happyReduction_218
5456happyReduction_218 happy_x_1
5457	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5458	happyIn98
5459		 (sL1 happy_var_1 (mj AnnNewtype happy_var_1,NewType)
5460	)}
5461
5462happyReduce_219 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5463happyReduce_219 = happySpecReduce_0  83# happyReduction_219
5464happyReduction_219  =  happyIn99
5465		 (noLoc     ([]               , Nothing)
5466	)
5467
5468happyReduce_220 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5469happyReduce_220 = happySpecReduce_2  83# happyReduction_220
5470happyReduction_220 happy_x_2
5471	happy_x_1
5472	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5473	case happyOut181 happy_x_2 of { (HappyWrap181 happy_var_2) ->
5474	happyIn99
5475		 (sLL happy_var_1 happy_var_2 ([mu AnnDcolon happy_var_1], Just happy_var_2)
5476	)}}
5477
5478happyReduce_221 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5479happyReduce_221 = happySpecReduce_0  84# happyReduction_221
5480happyReduction_221  =  happyIn100
5481		 (noLoc     ([]               , noLoc (NoSig noExtField)         )
5482	)
5483
5484happyReduce_222 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5485happyReduce_222 = happySpecReduce_2  84# happyReduction_222
5486happyReduction_222 happy_x_2
5487	happy_x_1
5488	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5489	case happyOut181 happy_x_2 of { (HappyWrap181 happy_var_2) ->
5490	happyIn100
5491		 (sLL happy_var_1 happy_var_2 ([mu AnnDcolon happy_var_1], sLL happy_var_1 happy_var_2 (KindSig noExtField happy_var_2))
5492	)}}
5493
5494happyReduce_223 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5495happyReduce_223 = happySpecReduce_0  85# happyReduction_223
5496happyReduction_223  =  happyIn101
5497		 (noLoc     ([]               , noLoc     (NoSig    noExtField)   )
5498	)
5499
5500happyReduce_224 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5501happyReduce_224 = happySpecReduce_2  85# happyReduction_224
5502happyReduction_224 happy_x_2
5503	happy_x_1
5504	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5505	case happyOut181 happy_x_2 of { (HappyWrap181 happy_var_2) ->
5506	happyIn101
5507		 (sLL happy_var_1 happy_var_2 ([mu AnnDcolon happy_var_1], sLL happy_var_1 happy_var_2 (KindSig  noExtField happy_var_2))
5508	)}}
5509
5510happyReduce_225 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5511happyReduce_225 = happySpecReduce_2  85# happyReduction_225
5512happyReduction_225 happy_x_2
5513	happy_x_1
5514	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5515	case happyOut176 happy_x_2 of { (HappyWrap176 happy_var_2) ->
5516	happyIn101
5517		 (sLL happy_var_1 happy_var_2 ([mj AnnEqual happy_var_1] , sLL happy_var_1 happy_var_2 (TyVarSig noExtField happy_var_2))
5518	)}}
5519
5520happyReduce_226 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5521happyReduce_226 = happySpecReduce_0  86# happyReduction_226
5522happyReduction_226  =  happyIn102
5523		 (noLoc ([], (noLoc (NoSig noExtField), Nothing))
5524	)
5525
5526happyReduce_227 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5527happyReduce_227 = happySpecReduce_2  86# happyReduction_227
5528happyReduction_227 happy_x_2
5529	happy_x_1
5530	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5531	case happyOut181 happy_x_2 of { (HappyWrap181 happy_var_2) ->
5532	happyIn102
5533		 (sLL happy_var_1 happy_var_2 ( [mu AnnDcolon happy_var_1]
5534                                 , (sLL happy_var_2 happy_var_2 (KindSig noExtField happy_var_2), Nothing))
5535	)}}
5536
5537happyReduce_228 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5538happyReduce_228 = happyReduce 4# 86# happyReduction_228
5539happyReduction_228 (happy_x_4 `HappyStk`
5540	happy_x_3 `HappyStk`
5541	happy_x_2 `HappyStk`
5542	happy_x_1 `HappyStk`
5543	happyRest)
5544	 = case happyOutTok happy_x_1 of { happy_var_1 ->
5545	case happyOut176 happy_x_2 of { (HappyWrap176 happy_var_2) ->
5546	case happyOutTok happy_x_3 of { happy_var_3 ->
5547	case happyOut88 happy_x_4 of { (HappyWrap88 happy_var_4) ->
5548	happyIn102
5549		 (sLL happy_var_1 happy_var_4 ([mj AnnEqual happy_var_1, mj AnnVbar happy_var_3]
5550                            , (sLL happy_var_1 happy_var_2 (TyVarSig noExtField happy_var_2), Just happy_var_4))
5551	) `HappyStk` happyRest}}}}
5552
5553happyReduce_229 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5554happyReduce_229 = happyMonadReduce 3# 87# happyReduction_229
5555happyReduction_229 (happy_x_3 `HappyStk`
5556	happy_x_2 `HappyStk`
5557	happy_x_1 `HappyStk`
5558	happyRest) tk
5559	 = happyThen ((case happyOut159 happy_x_1 of { (HappyWrap159 happy_var_1) ->
5560	case happyOutTok happy_x_2 of { happy_var_2 ->
5561	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
5562	( addAnnotation (gl happy_var_1) (toUnicodeAnn AnnDarrow happy_var_2) (gl happy_var_2)
5563                                       >> (return (sLL happy_var_1 happy_var_3 (Just happy_var_1, happy_var_3))))}}})
5564	) (\r -> happyReturn (happyIn103 r))
5565
5566happyReduce_230 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5567happyReduce_230 = happySpecReduce_1  87# happyReduction_230
5568happyReduction_230 happy_x_1
5569	 =  case happyOut161 happy_x_1 of { (HappyWrap161 happy_var_1) ->
5570	happyIn103
5571		 (sL1 happy_var_1 (Nothing, happy_var_1)
5572	)}
5573
5574happyReduce_231 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5575happyReduce_231 = happyMonadReduce 6# 88# happyReduction_231
5576happyReduction_231 (happy_x_6 `HappyStk`
5577	happy_x_5 `HappyStk`
5578	happy_x_4 `HappyStk`
5579	happy_x_3 `HappyStk`
5580	happy_x_2 `HappyStk`
5581	happy_x_1 `HappyStk`
5582	happyRest) tk
5583	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5584	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
5585	case happyOutTok happy_x_3 of { happy_var_3 ->
5586	case happyOut159 happy_x_4 of { (HappyWrap159 happy_var_4) ->
5587	case happyOutTok happy_x_5 of { happy_var_5 ->
5588	case happyOut161 happy_x_6 of { (HappyWrap161 happy_var_6) ->
5589	( hintExplicitForall happy_var_1
5590                                                       >> (addAnnotation (gl happy_var_4) (toUnicodeAnn AnnDarrow happy_var_5) (gl happy_var_5)
5591                                                           >> return (sLL happy_var_1 happy_var_6 ([mu AnnForall happy_var_1, mj AnnDot happy_var_3]
5592                                                                                , (Just happy_var_4, Just happy_var_2, happy_var_6)))
5593                                                          ))}}}}}})
5594	) (\r -> happyReturn (happyIn104 r))
5595
5596happyReduce_232 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5597happyReduce_232 = happyMonadReduce 4# 88# happyReduction_232
5598happyReduction_232 (happy_x_4 `HappyStk`
5599	happy_x_3 `HappyStk`
5600	happy_x_2 `HappyStk`
5601	happy_x_1 `HappyStk`
5602	happyRest) tk
5603	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5604	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
5605	case happyOutTok happy_x_3 of { happy_var_3 ->
5606	case happyOut161 happy_x_4 of { (HappyWrap161 happy_var_4) ->
5607	( hintExplicitForall happy_var_1
5608                                          >> return (sLL happy_var_1 happy_var_4 ([mu AnnForall happy_var_1, mj AnnDot happy_var_3]
5609                                                               , (Nothing, Just happy_var_2, happy_var_4))))}}}})
5610	) (\r -> happyReturn (happyIn104 r))
5611
5612happyReduce_233 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5613happyReduce_233 = happyMonadReduce 3# 88# happyReduction_233
5614happyReduction_233 (happy_x_3 `HappyStk`
5615	happy_x_2 `HappyStk`
5616	happy_x_1 `HappyStk`
5617	happyRest) tk
5618	 = happyThen ((case happyOut159 happy_x_1 of { (HappyWrap159 happy_var_1) ->
5619	case happyOutTok happy_x_2 of { happy_var_2 ->
5620	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
5621	( addAnnotation (gl happy_var_1) (toUnicodeAnn AnnDarrow happy_var_2) (gl happy_var_2)
5622                                       >> (return (sLL happy_var_1 happy_var_3([], (Just happy_var_1, Nothing, happy_var_3)))))}}})
5623	) (\r -> happyReturn (happyIn104 r))
5624
5625happyReduce_234 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5626happyReduce_234 = happySpecReduce_1  88# happyReduction_234
5627happyReduction_234 happy_x_1
5628	 =  case happyOut161 happy_x_1 of { (HappyWrap161 happy_var_1) ->
5629	happyIn104
5630		 (sL1 happy_var_1 ([], (Nothing, Nothing, happy_var_1))
5631	)}
5632
5633happyReduce_235 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5634happyReduce_235 = happyMonadReduce 4# 89# happyReduction_235
5635happyReduction_235 (happy_x_4 `HappyStk`
5636	happy_x_3 `HappyStk`
5637	happy_x_2 `HappyStk`
5638	happy_x_1 `HappyStk`
5639	happyRest) tk
5640	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5641	case happyOutTok happy_x_2 of { happy_var_2 ->
5642	case happyOutTok happy_x_3 of { happy_var_3 ->
5643	case happyOutTok happy_x_4 of { happy_var_4 ->
5644	( ajs (sLL happy_var_1 happy_var_4 (CType (getCTYPEs happy_var_1) (Just (Header (getSTRINGs happy_var_2) (getSTRING happy_var_2)))
5645                                        (getSTRINGs happy_var_3,getSTRING happy_var_3)))
5646                              [mo happy_var_1,mj AnnHeader happy_var_2,mj AnnVal happy_var_3,mc happy_var_4])}}}})
5647	) (\r -> happyReturn (happyIn105 r))
5648
5649happyReduce_236 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5650happyReduce_236 = happyMonadReduce 3# 89# happyReduction_236
5651happyReduction_236 (happy_x_3 `HappyStk`
5652	happy_x_2 `HappyStk`
5653	happy_x_1 `HappyStk`
5654	happyRest) tk
5655	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5656	case happyOutTok happy_x_2 of { happy_var_2 ->
5657	case happyOutTok happy_x_3 of { happy_var_3 ->
5658	( ajs (sLL happy_var_1 happy_var_3 (CType (getCTYPEs happy_var_1) Nothing (getSTRINGs happy_var_2, getSTRING happy_var_2)))
5659                              [mo happy_var_1,mj AnnVal happy_var_2,mc happy_var_3])}}})
5660	) (\r -> happyReturn (happyIn105 r))
5661
5662happyReduce_237 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5663happyReduce_237 = happySpecReduce_0  89# happyReduction_237
5664happyReduction_237  =  happyIn105
5665		 (Nothing
5666	)
5667
5668happyReduce_238 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5669happyReduce_238 = happyMonadReduce 5# 90# happyReduction_238
5670happyReduction_238 (happy_x_5 `HappyStk`
5671	happy_x_4 `HappyStk`
5672	happy_x_3 `HappyStk`
5673	happy_x_2 `HappyStk`
5674	happy_x_1 `HappyStk`
5675	happyRest) tk
5676	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5677	case happyOut86 happy_x_2 of { (HappyWrap86 happy_var_2) ->
5678	case happyOutTok happy_x_3 of { happy_var_3 ->
5679	case happyOut83 happy_x_4 of { (HappyWrap83 happy_var_4) ->
5680	case happyOut170 happy_x_5 of { (HappyWrap170 happy_var_5) ->
5681	( do { let { err = text "in the stand-alone deriving instance"
5682                                    <> colon <+> quotes (ppr happy_var_5) }
5683                      ; ams (sLL happy_var_1 (hsSigType happy_var_5)
5684                                 (DerivDecl noExtField (mkHsWildCardBndrs happy_var_5) happy_var_2 happy_var_4))
5685                            [mj AnnDeriving happy_var_1, mj AnnInstance happy_var_3] })}}}}})
5686	) (\r -> happyReturn (happyIn106 r))
5687
5688happyReduce_239 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5689happyReduce_239 = happyMonadReduce 4# 91# happyReduction_239
5690happyReduction_239 (happy_x_4 `HappyStk`
5691	happy_x_3 `HappyStk`
5692	happy_x_2 `HappyStk`
5693	happy_x_1 `HappyStk`
5694	happyRest) tk
5695	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5696	case happyOutTok happy_x_2 of { happy_var_2 ->
5697	case happyOut284 happy_x_3 of { (HappyWrap284 happy_var_3) ->
5698	case happyOut108 happy_x_4 of { (HappyWrap108 happy_var_4) ->
5699	( amms (mkRoleAnnotDecl (comb3 happy_var_1 happy_var_3 happy_var_4) happy_var_3 (reverse (unLoc happy_var_4)))
5700                  [mj AnnType happy_var_1,mj AnnRole happy_var_2])}}}})
5701	) (\r -> happyReturn (happyIn107 r))
5702
5703happyReduce_240 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5704happyReduce_240 = happySpecReduce_0  92# happyReduction_240
5705happyReduction_240  =  happyIn108
5706		 (noLoc []
5707	)
5708
5709happyReduce_241 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5710happyReduce_241 = happySpecReduce_1  92# happyReduction_241
5711happyReduction_241 happy_x_1
5712	 =  case happyOut109 happy_x_1 of { (HappyWrap109 happy_var_1) ->
5713	happyIn108
5714		 (happy_var_1
5715	)}
5716
5717happyReduce_242 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5718happyReduce_242 = happySpecReduce_1  93# happyReduction_242
5719happyReduction_242 happy_x_1
5720	 =  case happyOut110 happy_x_1 of { (HappyWrap110 happy_var_1) ->
5721	happyIn109
5722		 (sLL happy_var_1 happy_var_1 [happy_var_1]
5723	)}
5724
5725happyReduce_243 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5726happyReduce_243 = happySpecReduce_2  93# happyReduction_243
5727happyReduction_243 happy_x_2
5728	happy_x_1
5729	 =  case happyOut109 happy_x_1 of { (HappyWrap109 happy_var_1) ->
5730	case happyOut110 happy_x_2 of { (HappyWrap110 happy_var_2) ->
5731	happyIn109
5732		 (sLL happy_var_1 happy_var_2 $ happy_var_2 : unLoc happy_var_1
5733	)}}
5734
5735happyReduce_244 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5736happyReduce_244 = happySpecReduce_1  94# happyReduction_244
5737happyReduction_244 happy_x_1
5738	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5739	happyIn110
5740		 (sL1 happy_var_1 $ Just $ getVARID happy_var_1
5741	)}
5742
5743happyReduce_245 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5744happyReduce_245 = happySpecReduce_1  94# happyReduction_245
5745happyReduction_245 happy_x_1
5746	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
5747	happyIn110
5748		 (sL1 happy_var_1 Nothing
5749	)}
5750
5751happyReduce_246 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5752happyReduce_246 = happyMonadReduce 4# 95# happyReduction_246
5753happyReduction_246 (happy_x_4 `HappyStk`
5754	happy_x_3 `HappyStk`
5755	happy_x_2 `HappyStk`
5756	happy_x_1 `HappyStk`
5757	happyRest) tk
5758	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5759	case happyOut112 happy_x_2 of { (HappyWrap112 happy_var_2) ->
5760	case happyOutTok happy_x_3 of { happy_var_3 ->
5761	case happyOut249 happy_x_4 of { (HappyWrap249 happy_var_4) ->
5762	(      let (name, args,as ) = happy_var_2 in
5763                 ams (sLL happy_var_1 happy_var_4 . ValD noExtField $ mkPatSynBind name args happy_var_4
5764                                                    ImplicitBidirectional)
5765               (as ++ [mj AnnPattern happy_var_1, mj AnnEqual happy_var_3]))}}}})
5766	) (\r -> happyReturn (happyIn111 r))
5767
5768happyReduce_247 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5769happyReduce_247 = happyMonadReduce 4# 95# happyReduction_247
5770happyReduction_247 (happy_x_4 `HappyStk`
5771	happy_x_3 `HappyStk`
5772	happy_x_2 `HappyStk`
5773	happy_x_1 `HappyStk`
5774	happyRest) tk
5775	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5776	case happyOut112 happy_x_2 of { (HappyWrap112 happy_var_2) ->
5777	case happyOutTok happy_x_3 of { happy_var_3 ->
5778	case happyOut249 happy_x_4 of { (HappyWrap249 happy_var_4) ->
5779	(    let (name, args, as) = happy_var_2 in
5780               ams (sLL happy_var_1 happy_var_4 . ValD noExtField $ mkPatSynBind name args happy_var_4 Unidirectional)
5781               (as ++ [mj AnnPattern happy_var_1,mu AnnLarrow happy_var_3]))}}}})
5782	) (\r -> happyReturn (happyIn111 r))
5783
5784happyReduce_248 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5785happyReduce_248 = happyMonadReduce 5# 95# happyReduction_248
5786happyReduction_248 (happy_x_5 `HappyStk`
5787	happy_x_4 `HappyStk`
5788	happy_x_3 `HappyStk`
5789	happy_x_2 `HappyStk`
5790	happy_x_1 `HappyStk`
5791	happyRest) tk
5792	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5793	case happyOut112 happy_x_2 of { (HappyWrap112 happy_var_2) ->
5794	case happyOutTok happy_x_3 of { happy_var_3 ->
5795	case happyOut249 happy_x_4 of { (HappyWrap249 happy_var_4) ->
5796	case happyOut115 happy_x_5 of { (HappyWrap115 happy_var_5) ->
5797	( do { let (name, args, as) = happy_var_2
5798                  ; mg <- mkPatSynMatchGroup name (snd $ unLoc happy_var_5)
5799                  ; ams (sLL happy_var_1 happy_var_5 . ValD noExtField $
5800                           mkPatSynBind name args happy_var_4 (ExplicitBidirectional mg))
5801                       (as ++ ((mj AnnPattern happy_var_1:mu AnnLarrow happy_var_3:(fst $ unLoc happy_var_5))) )
5802                   })}}}}})
5803	) (\r -> happyReturn (happyIn111 r))
5804
5805happyReduce_249 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5806happyReduce_249 = happySpecReduce_2  96# happyReduction_249
5807happyReduction_249 happy_x_2
5808	happy_x_1
5809	 =  case happyOut276 happy_x_1 of { (HappyWrap276 happy_var_1) ->
5810	case happyOut113 happy_x_2 of { (HappyWrap113 happy_var_2) ->
5811	happyIn112
5812		 ((happy_var_1, PrefixCon happy_var_2, [])
5813	)}}
5814
5815happyReduce_250 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5816happyReduce_250 = happySpecReduce_3  96# happyReduction_250
5817happyReduction_250 happy_x_3
5818	happy_x_2
5819	happy_x_1
5820	 =  case happyOut305 happy_x_1 of { (HappyWrap305 happy_var_1) ->
5821	case happyOut280 happy_x_2 of { (HappyWrap280 happy_var_2) ->
5822	case happyOut305 happy_x_3 of { (HappyWrap305 happy_var_3) ->
5823	happyIn112
5824		 ((happy_var_2, InfixCon happy_var_1 happy_var_3, [])
5825	)}}}
5826
5827happyReduce_251 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5828happyReduce_251 = happyReduce 4# 96# happyReduction_251
5829happyReduction_251 (happy_x_4 `HappyStk`
5830	happy_x_3 `HappyStk`
5831	happy_x_2 `HappyStk`
5832	happy_x_1 `HappyStk`
5833	happyRest)
5834	 = case happyOut276 happy_x_1 of { (HappyWrap276 happy_var_1) ->
5835	case happyOutTok happy_x_2 of { happy_var_2 ->
5836	case happyOut114 happy_x_3 of { (HappyWrap114 happy_var_3) ->
5837	case happyOutTok happy_x_4 of { happy_var_4 ->
5838	happyIn112
5839		 ((happy_var_1, RecCon happy_var_3, [moc happy_var_2, mcc happy_var_4] )
5840	) `HappyStk` happyRest}}}}
5841
5842happyReduce_252 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5843happyReduce_252 = happySpecReduce_0  97# happyReduction_252
5844happyReduction_252  =  happyIn113
5845		 ([]
5846	)
5847
5848happyReduce_253 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5849happyReduce_253 = happySpecReduce_2  97# happyReduction_253
5850happyReduction_253 happy_x_2
5851	happy_x_1
5852	 =  case happyOut305 happy_x_1 of { (HappyWrap305 happy_var_1) ->
5853	case happyOut113 happy_x_2 of { (HappyWrap113 happy_var_2) ->
5854	happyIn113
5855		 (happy_var_1 : happy_var_2
5856	)}}
5857
5858happyReduce_254 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5859happyReduce_254 = happySpecReduce_1  98# happyReduction_254
5860happyReduction_254 happy_x_1
5861	 =  case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
5862	happyIn114
5863		 ([RecordPatSynField happy_var_1 happy_var_1]
5864	)}
5865
5866happyReduce_255 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5867happyReduce_255 = happyMonadReduce 3# 98# happyReduction_255
5868happyReduction_255 (happy_x_3 `HappyStk`
5869	happy_x_2 `HappyStk`
5870	happy_x_1 `HappyStk`
5871	happyRest) tk
5872	 = happyThen ((case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
5873	case happyOutTok happy_x_2 of { happy_var_2 ->
5874	case happyOut114 happy_x_3 of { (HappyWrap114 happy_var_3) ->
5875	( addAnnotation (getLoc happy_var_1) AnnComma (getLoc happy_var_2) >>
5876                                         return ((RecordPatSynField happy_var_1 happy_var_1) : happy_var_3 ))}}})
5877	) (\r -> happyReturn (happyIn114 r))
5878
5879happyReduce_256 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5880happyReduce_256 = happyReduce 4# 99# happyReduction_256
5881happyReduction_256 (happy_x_4 `HappyStk`
5882	happy_x_3 `HappyStk`
5883	happy_x_2 `HappyStk`
5884	happy_x_1 `HappyStk`
5885	happyRest)
5886	 = case happyOutTok happy_x_1 of { happy_var_1 ->
5887	case happyOutTok happy_x_2 of { happy_var_2 ->
5888	case happyOut125 happy_x_3 of { (HappyWrap125 happy_var_3) ->
5889	case happyOutTok happy_x_4 of { happy_var_4 ->
5890	happyIn115
5891		 (sLL happy_var_1 happy_var_4 ((mj AnnWhere happy_var_1:moc happy_var_2
5892                                           :mcc happy_var_4:(fst $ unLoc happy_var_3)),sL1 happy_var_3 (snd $ unLoc happy_var_3))
5893	) `HappyStk` happyRest}}}}
5894
5895happyReduce_257 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5896happyReduce_257 = happyReduce 4# 99# happyReduction_257
5897happyReduction_257 (happy_x_4 `HappyStk`
5898	happy_x_3 `HappyStk`
5899	happy_x_2 `HappyStk`
5900	happy_x_1 `HappyStk`
5901	happyRest)
5902	 = case happyOutTok happy_x_1 of { happy_var_1 ->
5903	case happyOut125 happy_x_3 of { (HappyWrap125 happy_var_3) ->
5904	happyIn115
5905		 (cL (comb2 happy_var_1 happy_var_3) ((mj AnnWhere happy_var_1:(fst $ unLoc happy_var_3))
5906                                          ,sL1 happy_var_3 (snd $ unLoc happy_var_3))
5907	) `HappyStk` happyRest}}
5908
5909happyReduce_258 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5910happyReduce_258 = happyMonadReduce 4# 100# happyReduction_258
5911happyReduction_258 (happy_x_4 `HappyStk`
5912	happy_x_3 `HappyStk`
5913	happy_x_2 `HappyStk`
5914	happy_x_1 `HappyStk`
5915	happyRest) tk
5916	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5917	case happyOut277 happy_x_2 of { (HappyWrap277 happy_var_2) ->
5918	case happyOutTok happy_x_3 of { happy_var_3 ->
5919	case happyOut150 happy_x_4 of { (HappyWrap150 happy_var_4) ->
5920	( ams (sLL happy_var_1 happy_var_4 $ PatSynSig noExtField (unLoc happy_var_2) (mkLHsSigType happy_var_4))
5921                          [mj AnnPattern happy_var_1, mu AnnDcolon happy_var_3])}}}})
5922	) (\r -> happyReturn (happyIn116 r))
5923
5924happyReduce_259 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5925happyReduce_259 = happySpecReduce_1  101# happyReduction_259
5926happyReduction_259 happy_x_1
5927	 =  case happyOut94 happy_x_1 of { (HappyWrap94 happy_var_1) ->
5928	happyIn117
5929		 (happy_var_1
5930	)}
5931
5932happyReduce_260 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5933happyReduce_260 = happySpecReduce_1  101# happyReduction_260
5934happyReduction_260 happy_x_1
5935	 =  case happyOut201 happy_x_1 of { (HappyWrap201 happy_var_1) ->
5936	happyIn117
5937		 (happy_var_1
5938	)}
5939
5940happyReduce_261 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5941happyReduce_261 = happyMonadReduce 4# 101# happyReduction_261
5942happyReduction_261 (happy_x_4 `HappyStk`
5943	happy_x_3 `HappyStk`
5944	happy_x_2 `HappyStk`
5945	happy_x_1 `HappyStk`
5946	happyRest) tk
5947	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
5948	case happyOut210 happy_x_2 of { (HappyWrap210 happy_var_2) ->
5949	case happyOutTok happy_x_3 of { happy_var_3 ->
5950	case happyOut150 happy_x_4 of { (HappyWrap150 happy_var_4) ->
5951	( runECP_P happy_var_2 >>= \ happy_var_2 ->
5952                       do { v <- checkValSigLhs happy_var_2
5953                          ; let err = text "in default signature" <> colon <+>
5954                                      quotes (ppr happy_var_2)
5955                          ; ams (sLL happy_var_1 happy_var_4 $ SigD noExtField $ ClassOpSig noExtField True [v] $ mkLHsSigType happy_var_4)
5956                                [mj AnnDefault happy_var_1,mu AnnDcolon happy_var_3] })}}}})
5957	) (\r -> happyReturn (happyIn117 r))
5958
5959happyReduce_262 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5960happyReduce_262 = happyMonadReduce 3# 102# happyReduction_262
5961happyReduction_262 (happy_x_3 `HappyStk`
5962	happy_x_2 `HappyStk`
5963	happy_x_1 `HappyStk`
5964	happyRest) tk
5965	 = happyThen ((case happyOut118 happy_x_1 of { (HappyWrap118 happy_var_1) ->
5966	case happyOutTok happy_x_2 of { happy_var_2 ->
5967	case happyOut117 happy_x_3 of { (HappyWrap117 happy_var_3) ->
5968	( if isNilOL (snd $ unLoc happy_var_1)
5969                                             then return (sLL happy_var_1 happy_var_3 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
5970                                                                    , unitOL happy_var_3))
5971                                             else ams (lastOL (snd $ unLoc happy_var_1)) [mj AnnSemi happy_var_2]
5972                                           >> return (sLL happy_var_1 happy_var_3 (fst $ unLoc happy_var_1
5973                                                                ,(snd $ unLoc happy_var_1) `appOL` unitOL happy_var_3)))}}})
5974	) (\r -> happyReturn (happyIn118 r))
5975
5976happyReduce_263 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5977happyReduce_263 = happyMonadReduce 2# 102# happyReduction_263
5978happyReduction_263 (happy_x_2 `HappyStk`
5979	happy_x_1 `HappyStk`
5980	happyRest) tk
5981	 = happyThen ((case happyOut118 happy_x_1 of { (HappyWrap118 happy_var_1) ->
5982	case happyOutTok happy_x_2 of { happy_var_2 ->
5983	( if isNilOL (snd $ unLoc happy_var_1)
5984                                             then return (sLL happy_var_1 happy_var_2 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
5985                                                                                   ,snd $ unLoc happy_var_1))
5986                                             else ams (lastOL (snd $ unLoc happy_var_1)) [mj AnnSemi happy_var_2]
5987                                           >> return (sLL happy_var_1 happy_var_2  (unLoc happy_var_1)))}})
5988	) (\r -> happyReturn (happyIn118 r))
5989
5990happyReduce_264 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5991happyReduce_264 = happySpecReduce_1  102# happyReduction_264
5992happyReduction_264 happy_x_1
5993	 =  case happyOut117 happy_x_1 of { (HappyWrap117 happy_var_1) ->
5994	happyIn118
5995		 (sL1 happy_var_1 ([], unitOL happy_var_1)
5996	)}
5997
5998happyReduce_265 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
5999happyReduce_265 = happySpecReduce_0  102# happyReduction_265
6000happyReduction_265  =  happyIn118
6001		 (noLoc ([],nilOL)
6002	)
6003
6004happyReduce_266 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6005happyReduce_266 = happySpecReduce_3  103# happyReduction_266
6006happyReduction_266 happy_x_3
6007	happy_x_2
6008	happy_x_1
6009	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6010	case happyOut118 happy_x_2 of { (HappyWrap118 happy_var_2) ->
6011	case happyOutTok happy_x_3 of { happy_var_3 ->
6012	happyIn119
6013		 (sLL happy_var_1 happy_var_3 (moc happy_var_1:mcc happy_var_3:(fst $ unLoc happy_var_2)
6014                                             ,snd $ unLoc happy_var_2)
6015	)}}}
6016
6017happyReduce_267 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6018happyReduce_267 = happySpecReduce_3  103# happyReduction_267
6019happyReduction_267 happy_x_3
6020	happy_x_2
6021	happy_x_1
6022	 =  case happyOut118 happy_x_2 of { (HappyWrap118 happy_var_2) ->
6023	happyIn119
6024		 (happy_var_2
6025	)}
6026
6027happyReduce_268 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6028happyReduce_268 = happySpecReduce_2  104# happyReduction_268
6029happyReduction_268 happy_x_2
6030	happy_x_1
6031	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6032	case happyOut119 happy_x_2 of { (HappyWrap119 happy_var_2) ->
6033	happyIn120
6034		 (sLL happy_var_1 happy_var_2 (mj AnnWhere happy_var_1:(fst $ unLoc happy_var_2)
6035                                             ,snd $ unLoc happy_var_2)
6036	)}}
6037
6038happyReduce_269 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6039happyReduce_269 = happySpecReduce_0  104# happyReduction_269
6040happyReduction_269  =  happyIn120
6041		 (noLoc ([],nilOL)
6042	)
6043
6044happyReduce_270 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6045happyReduce_270 = happySpecReduce_1  105# happyReduction_270
6046happyReduction_270 happy_x_1
6047	 =  case happyOut97 happy_x_1 of { (HappyWrap97 happy_var_1) ->
6048	happyIn121
6049		 (sLL happy_var_1 happy_var_1 (unitOL (sL1 happy_var_1 (InstD noExtField (unLoc happy_var_1))))
6050	)}
6051
6052happyReduce_271 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6053happyReduce_271 = happySpecReduce_1  105# happyReduction_271
6054happyReduction_271 happy_x_1
6055	 =  case happyOut201 happy_x_1 of { (HappyWrap201 happy_var_1) ->
6056	happyIn121
6057		 (sLL happy_var_1 happy_var_1 (unitOL happy_var_1)
6058	)}
6059
6060happyReduce_272 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6061happyReduce_272 = happyMonadReduce 3# 106# happyReduction_272
6062happyReduction_272 (happy_x_3 `HappyStk`
6063	happy_x_2 `HappyStk`
6064	happy_x_1 `HappyStk`
6065	happyRest) tk
6066	 = happyThen ((case happyOut122 happy_x_1 of { (HappyWrap122 happy_var_1) ->
6067	case happyOutTok happy_x_2 of { happy_var_2 ->
6068	case happyOut121 happy_x_3 of { (HappyWrap121 happy_var_3) ->
6069	( if isNilOL (snd $ unLoc happy_var_1)
6070                                             then return (sLL happy_var_1 happy_var_3 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
6071                                                                    , unLoc happy_var_3))
6072                                             else ams (lastOL $ snd $ unLoc happy_var_1) [mj AnnSemi happy_var_2]
6073                                           >> return
6074                                            (sLL happy_var_1 happy_var_3 (fst $ unLoc happy_var_1
6075                                                       ,(snd $ unLoc happy_var_1) `appOL` unLoc happy_var_3)))}}})
6076	) (\r -> happyReturn (happyIn122 r))
6077
6078happyReduce_273 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6079happyReduce_273 = happyMonadReduce 2# 106# happyReduction_273
6080happyReduction_273 (happy_x_2 `HappyStk`
6081	happy_x_1 `HappyStk`
6082	happyRest) tk
6083	 = happyThen ((case happyOut122 happy_x_1 of { (HappyWrap122 happy_var_1) ->
6084	case happyOutTok happy_x_2 of { happy_var_2 ->
6085	( if isNilOL (snd $ unLoc happy_var_1)
6086                                             then return (sLL happy_var_1 happy_var_2 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
6087                                                                                   ,snd $ unLoc happy_var_1))
6088                                             else ams (lastOL $ snd $ unLoc happy_var_1) [mj AnnSemi happy_var_2]
6089                                           >> return (sLL happy_var_1 happy_var_2 (unLoc happy_var_1)))}})
6090	) (\r -> happyReturn (happyIn122 r))
6091
6092happyReduce_274 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6093happyReduce_274 = happySpecReduce_1  106# happyReduction_274
6094happyReduction_274 happy_x_1
6095	 =  case happyOut121 happy_x_1 of { (HappyWrap121 happy_var_1) ->
6096	happyIn122
6097		 (sL1 happy_var_1 ([],unLoc happy_var_1)
6098	)}
6099
6100happyReduce_275 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6101happyReduce_275 = happySpecReduce_0  106# happyReduction_275
6102happyReduction_275  =  happyIn122
6103		 (noLoc ([],nilOL)
6104	)
6105
6106happyReduce_276 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6107happyReduce_276 = happySpecReduce_3  107# happyReduction_276
6108happyReduction_276 happy_x_3
6109	happy_x_2
6110	happy_x_1
6111	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6112	case happyOut122 happy_x_2 of { (HappyWrap122 happy_var_2) ->
6113	case happyOutTok happy_x_3 of { happy_var_3 ->
6114	happyIn123
6115		 (sLL happy_var_1 happy_var_3 (moc happy_var_1:mcc happy_var_3:(fst $ unLoc happy_var_2),snd $ unLoc happy_var_2)
6116	)}}}
6117
6118happyReduce_277 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6119happyReduce_277 = happySpecReduce_3  107# happyReduction_277
6120happyReduction_277 happy_x_3
6121	happy_x_2
6122	happy_x_1
6123	 =  case happyOut122 happy_x_2 of { (HappyWrap122 happy_var_2) ->
6124	happyIn123
6125		 (cL (gl happy_var_2) (unLoc happy_var_2)
6126	)}
6127
6128happyReduce_278 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6129happyReduce_278 = happySpecReduce_2  108# happyReduction_278
6130happyReduction_278 happy_x_2
6131	happy_x_1
6132	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6133	case happyOut123 happy_x_2 of { (HappyWrap123 happy_var_2) ->
6134	happyIn124
6135		 (sLL happy_var_1 happy_var_2 (mj AnnWhere happy_var_1:(fst $ unLoc happy_var_2)
6136                                             ,(snd $ unLoc happy_var_2))
6137	)}}
6138
6139happyReduce_279 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6140happyReduce_279 = happySpecReduce_0  108# happyReduction_279
6141happyReduction_279  =  happyIn124
6142		 (noLoc ([],nilOL)
6143	)
6144
6145happyReduce_280 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6146happyReduce_280 = happyMonadReduce 3# 109# happyReduction_280
6147happyReduction_280 (happy_x_3 `HappyStk`
6148	happy_x_2 `HappyStk`
6149	happy_x_1 `HappyStk`
6150	happyRest) tk
6151	 = happyThen ((case happyOut125 happy_x_1 of { (HappyWrap125 happy_var_1) ->
6152	case happyOutTok happy_x_2 of { happy_var_2 ->
6153	case happyOut201 happy_x_3 of { (HappyWrap201 happy_var_3) ->
6154	( if isNilOL (snd $ unLoc happy_var_1)
6155                                 then return (sLL happy_var_1 happy_var_3 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
6156                                                        , unitOL happy_var_3))
6157                                 else do ams (lastOL $ snd $ unLoc happy_var_1) [mj AnnSemi happy_var_2]
6158                                           >> return (
6159                                          let { this = unitOL happy_var_3;
6160                                                rest = snd $ unLoc happy_var_1;
6161                                                these = rest `appOL` this }
6162                                          in rest `seq` this `seq` these `seq`
6163                                             (sLL happy_var_1 happy_var_3 (fst $ unLoc happy_var_1,these))))}}})
6164	) (\r -> happyReturn (happyIn125 r))
6165
6166happyReduce_281 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6167happyReduce_281 = happyMonadReduce 2# 109# happyReduction_281
6168happyReduction_281 (happy_x_2 `HappyStk`
6169	happy_x_1 `HappyStk`
6170	happyRest) tk
6171	 = happyThen ((case happyOut125 happy_x_1 of { (HappyWrap125 happy_var_1) ->
6172	case happyOutTok happy_x_2 of { happy_var_2 ->
6173	( if isNilOL (snd $ unLoc happy_var_1)
6174                                  then return (sLL happy_var_1 happy_var_2 ((mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
6175                                                          ,snd $ unLoc happy_var_1)))
6176                                  else ams (lastOL $ snd $ unLoc happy_var_1) [mj AnnSemi happy_var_2]
6177                                           >> return (sLL happy_var_1 happy_var_2 (unLoc happy_var_1)))}})
6178	) (\r -> happyReturn (happyIn125 r))
6179
6180happyReduce_282 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6181happyReduce_282 = happySpecReduce_1  109# happyReduction_282
6182happyReduction_282 happy_x_1
6183	 =  case happyOut201 happy_x_1 of { (HappyWrap201 happy_var_1) ->
6184	happyIn125
6185		 (sL1 happy_var_1 ([], unitOL happy_var_1)
6186	)}
6187
6188happyReduce_283 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6189happyReduce_283 = happySpecReduce_0  109# happyReduction_283
6190happyReduction_283  =  happyIn125
6191		 (noLoc ([],nilOL)
6192	)
6193
6194happyReduce_284 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6195happyReduce_284 = happySpecReduce_3  110# happyReduction_284
6196happyReduction_284 happy_x_3
6197	happy_x_2
6198	happy_x_1
6199	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6200	case happyOut125 happy_x_2 of { (HappyWrap125 happy_var_2) ->
6201	case happyOutTok happy_x_3 of { happy_var_3 ->
6202	happyIn126
6203		 (sLL happy_var_1 happy_var_3 (moc happy_var_1:mcc happy_var_3:(fst $ unLoc happy_var_2)
6204                                                   ,sL1 happy_var_2 $ snd $ unLoc happy_var_2)
6205	)}}}
6206
6207happyReduce_285 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6208happyReduce_285 = happySpecReduce_3  110# happyReduction_285
6209happyReduction_285 happy_x_3
6210	happy_x_2
6211	happy_x_1
6212	 =  case happyOut125 happy_x_2 of { (HappyWrap125 happy_var_2) ->
6213	happyIn126
6214		 (cL (gl happy_var_2) (fst $ unLoc happy_var_2,sL1 happy_var_2 $ snd $ unLoc happy_var_2)
6215	)}
6216
6217happyReduce_286 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6218happyReduce_286 = happyMonadReduce 1# 111# happyReduction_286
6219happyReduction_286 (happy_x_1 `HappyStk`
6220	happyRest) tk
6221	 = happyThen ((case happyOut126 happy_x_1 of { (HappyWrap126 happy_var_1) ->
6222	( do { val_binds <- cvBindGroup (unLoc $ snd $ unLoc happy_var_1)
6223                                  ; return (sL1 happy_var_1 (fst $ unLoc happy_var_1
6224                                                    ,sL1 happy_var_1 $ HsValBinds noExtField val_binds)) })})
6225	) (\r -> happyReturn (happyIn127 r))
6226
6227happyReduce_287 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6228happyReduce_287 = happySpecReduce_3  111# happyReduction_287
6229happyReduction_287 happy_x_3
6230	happy_x_2
6231	happy_x_1
6232	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6233	case happyOut262 happy_x_2 of { (HappyWrap262 happy_var_2) ->
6234	case happyOutTok happy_x_3 of { happy_var_3 ->
6235	happyIn127
6236		 (sLL happy_var_1 happy_var_3 ([moc happy_var_1,mcc happy_var_3]
6237                                             ,sL1 happy_var_2 $ HsIPBinds noExtField (IPBinds noExtField (reverse $ unLoc happy_var_2)))
6238	)}}}
6239
6240happyReduce_288 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6241happyReduce_288 = happySpecReduce_3  111# happyReduction_288
6242happyReduction_288 happy_x_3
6243	happy_x_2
6244	happy_x_1
6245	 =  case happyOut262 happy_x_2 of { (HappyWrap262 happy_var_2) ->
6246	happyIn127
6247		 (cL (getLoc happy_var_2) ([]
6248                                            ,sL1 happy_var_2 $ HsIPBinds noExtField (IPBinds noExtField (reverse $ unLoc happy_var_2)))
6249	)}
6250
6251happyReduce_289 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6252happyReduce_289 = happySpecReduce_2  112# happyReduction_289
6253happyReduction_289 happy_x_2
6254	happy_x_1
6255	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6256	case happyOut127 happy_x_2 of { (HappyWrap127 happy_var_2) ->
6257	happyIn128
6258		 (sLL happy_var_1 happy_var_2 (mj AnnWhere happy_var_1 : (fst $ unLoc happy_var_2)
6259                                             ,snd $ unLoc happy_var_2)
6260	)}}
6261
6262happyReduce_290 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6263happyReduce_290 = happySpecReduce_0  112# happyReduction_290
6264happyReduction_290  =  happyIn128
6265		 (noLoc ([],noLoc emptyLocalBinds)
6266	)
6267
6268happyReduce_291 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6269happyReduce_291 = happyMonadReduce 3# 113# happyReduction_291
6270happyReduction_291 (happy_x_3 `HappyStk`
6271	happy_x_2 `HappyStk`
6272	happy_x_1 `HappyStk`
6273	happyRest) tk
6274	 = happyThen ((case happyOut129 happy_x_1 of { (HappyWrap129 happy_var_1) ->
6275	case happyOutTok happy_x_2 of { happy_var_2 ->
6276	case happyOut130 happy_x_3 of { (HappyWrap130 happy_var_3) ->
6277	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6278                                          >> return (happy_var_1 `snocOL` happy_var_3))}}})
6279	) (\r -> happyReturn (happyIn129 r))
6280
6281happyReduce_292 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6282happyReduce_292 = happyMonadReduce 2# 113# happyReduction_292
6283happyReduction_292 (happy_x_2 `HappyStk`
6284	happy_x_1 `HappyStk`
6285	happyRest) tk
6286	 = happyThen ((case happyOut129 happy_x_1 of { (HappyWrap129 happy_var_1) ->
6287	case happyOutTok happy_x_2 of { happy_var_2 ->
6288	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6289                                          >> return happy_var_1)}})
6290	) (\r -> happyReturn (happyIn129 r))
6291
6292happyReduce_293 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6293happyReduce_293 = happySpecReduce_1  113# happyReduction_293
6294happyReduction_293 happy_x_1
6295	 =  case happyOut130 happy_x_1 of { (HappyWrap130 happy_var_1) ->
6296	happyIn129
6297		 (unitOL happy_var_1
6298	)}
6299
6300happyReduce_294 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6301happyReduce_294 = happySpecReduce_0  113# happyReduction_294
6302happyReduction_294  =  happyIn129
6303		 (nilOL
6304	)
6305
6306happyReduce_295 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6307happyReduce_295 = happyMonadReduce 6# 114# happyReduction_295
6308happyReduction_295 (happy_x_6 `HappyStk`
6309	happy_x_5 `HappyStk`
6310	happy_x_4 `HappyStk`
6311	happy_x_3 `HappyStk`
6312	happy_x_2 `HappyStk`
6313	happy_x_1 `HappyStk`
6314	happyRest) tk
6315	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6316	case happyOut131 happy_x_2 of { (HappyWrap131 happy_var_2) ->
6317	case happyOut133 happy_x_3 of { (HappyWrap133 happy_var_3) ->
6318	case happyOut210 happy_x_4 of { (HappyWrap210 happy_var_4) ->
6319	case happyOutTok happy_x_5 of { happy_var_5 ->
6320	case happyOut209 happy_x_6 of { (HappyWrap209 happy_var_6) ->
6321	(runECP_P happy_var_4 >>= \ happy_var_4 ->
6322           runECP_P happy_var_6 >>= \ happy_var_6 ->
6323           ams (sLL happy_var_1 happy_var_6 $ HsRule { rd_ext = noExtField
6324                                   , rd_name = cL (gl happy_var_1) (getSTRINGs happy_var_1, getSTRING happy_var_1)
6325                                   , rd_act = (snd happy_var_2) `orElse` AlwaysActive
6326                                   , rd_tyvs = sndOf3 happy_var_3, rd_tmvs = thdOf3 happy_var_3
6327                                   , rd_lhs = happy_var_4, rd_rhs = happy_var_6 })
6328               (mj AnnEqual happy_var_5 : (fst happy_var_2) ++ (fstOf3 happy_var_3)))}}}}}})
6329	) (\r -> happyReturn (happyIn130 r))
6330
6331happyReduce_296 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6332happyReduce_296 = happySpecReduce_0  115# happyReduction_296
6333happyReduction_296  =  happyIn131
6334		 (([],Nothing)
6335	)
6336
6337happyReduce_297 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6338happyReduce_297 = happySpecReduce_1  115# happyReduction_297
6339happyReduction_297 happy_x_1
6340	 =  case happyOut132 happy_x_1 of { (HappyWrap132 happy_var_1) ->
6341	happyIn131
6342		 ((fst happy_var_1,Just (snd happy_var_1))
6343	)}
6344
6345happyReduce_298 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6346happyReduce_298 = happySpecReduce_3  116# happyReduction_298
6347happyReduction_298 happy_x_3
6348	happy_x_2
6349	happy_x_1
6350	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6351	case happyOutTok happy_x_2 of { happy_var_2 ->
6352	case happyOutTok happy_x_3 of { happy_var_3 ->
6353	happyIn132
6354		 (([mos happy_var_1,mj AnnVal happy_var_2,mcs happy_var_3]
6355                                  ,ActiveAfter  (getINTEGERs happy_var_2) (fromInteger (il_value (getINTEGER happy_var_2))))
6356	)}}}
6357
6358happyReduce_299 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6359happyReduce_299 = happyReduce 4# 116# happyReduction_299
6360happyReduction_299 (happy_x_4 `HappyStk`
6361	happy_x_3 `HappyStk`
6362	happy_x_2 `HappyStk`
6363	happy_x_1 `HappyStk`
6364	happyRest)
6365	 = case happyOutTok happy_x_1 of { happy_var_1 ->
6366	case happyOutTok happy_x_2 of { happy_var_2 ->
6367	case happyOutTok happy_x_3 of { happy_var_3 ->
6368	case happyOutTok happy_x_4 of { happy_var_4 ->
6369	happyIn132
6370		 (([mos happy_var_1,mj AnnTilde happy_var_2,mj AnnVal happy_var_3,mcs happy_var_4]
6371                                  ,ActiveBefore (getINTEGERs happy_var_3) (fromInteger (il_value (getINTEGER happy_var_3))))
6372	) `HappyStk` happyRest}}}}
6373
6374happyReduce_300 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6375happyReduce_300 = happySpecReduce_3  116# happyReduction_300
6376happyReduction_300 happy_x_3
6377	happy_x_2
6378	happy_x_1
6379	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6380	case happyOutTok happy_x_2 of { happy_var_2 ->
6381	case happyOutTok happy_x_3 of { happy_var_3 ->
6382	happyIn132
6383		 (([mos happy_var_1,mj AnnTilde happy_var_2,mcs happy_var_3]
6384                                  ,NeverActive)
6385	)}}}
6386
6387happyReduce_301 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6388happyReduce_301 = happyMonadReduce 6# 117# happyReduction_301
6389happyReduction_301 (happy_x_6 `HappyStk`
6390	happy_x_5 `HappyStk`
6391	happy_x_4 `HappyStk`
6392	happy_x_3 `HappyStk`
6393	happy_x_2 `HappyStk`
6394	happy_x_1 `HappyStk`
6395	happyRest) tk
6396	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6397	case happyOut134 happy_x_2 of { (HappyWrap134 happy_var_2) ->
6398	case happyOutTok happy_x_3 of { happy_var_3 ->
6399	case happyOutTok happy_x_4 of { happy_var_4 ->
6400	case happyOut134 happy_x_5 of { (HappyWrap134 happy_var_5) ->
6401	case happyOutTok happy_x_6 of { happy_var_6 ->
6402	( let tyvs = mkRuleTyVarBndrs happy_var_2
6403                                                              in hintExplicitForall happy_var_1
6404                                                              >> checkRuleTyVarBndrNames (mkRuleTyVarBndrs happy_var_2)
6405                                                              >> return ([mu AnnForall happy_var_1,mj AnnDot happy_var_3,
6406                                                                          mu AnnForall happy_var_4,mj AnnDot happy_var_6],
6407                                                                         Just (mkRuleTyVarBndrs happy_var_2), mkRuleBndrs happy_var_5))}}}}}})
6408	) (\r -> happyReturn (happyIn133 r))
6409
6410happyReduce_302 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6411happyReduce_302 = happySpecReduce_3  117# happyReduction_302
6412happyReduction_302 happy_x_3
6413	happy_x_2
6414	happy_x_1
6415	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6416	case happyOut134 happy_x_2 of { (HappyWrap134 happy_var_2) ->
6417	case happyOutTok happy_x_3 of { happy_var_3 ->
6418	happyIn133
6419		 (([mu AnnForall happy_var_1,mj AnnDot happy_var_3],
6420                                                              Nothing, mkRuleBndrs happy_var_2)
6421	)}}}
6422
6423happyReduce_303 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6424happyReduce_303 = happySpecReduce_0  117# happyReduction_303
6425happyReduction_303  =  happyIn133
6426		 (([], Nothing, [])
6427	)
6428
6429happyReduce_304 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6430happyReduce_304 = happySpecReduce_2  118# happyReduction_304
6431happyReduction_304 happy_x_2
6432	happy_x_1
6433	 =  case happyOut135 happy_x_1 of { (HappyWrap135 happy_var_1) ->
6434	case happyOut134 happy_x_2 of { (HappyWrap134 happy_var_2) ->
6435	happyIn134
6436		 (happy_var_1 : happy_var_2
6437	)}}
6438
6439happyReduce_305 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6440happyReduce_305 = happySpecReduce_0  118# happyReduction_305
6441happyReduction_305  =  happyIn134
6442		 ([]
6443	)
6444
6445happyReduce_306 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6446happyReduce_306 = happySpecReduce_1  119# happyReduction_306
6447happyReduction_306 happy_x_1
6448	 =  case happyOut305 happy_x_1 of { (HappyWrap305 happy_var_1) ->
6449	happyIn135
6450		 (sLL happy_var_1 happy_var_1 (RuleTyTmVar happy_var_1 Nothing)
6451	)}
6452
6453happyReduce_307 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6454happyReduce_307 = happyMonadReduce 5# 119# happyReduction_307
6455happyReduction_307 (happy_x_5 `HappyStk`
6456	happy_x_4 `HappyStk`
6457	happy_x_3 `HappyStk`
6458	happy_x_2 `HappyStk`
6459	happy_x_1 `HappyStk`
6460	happyRest) tk
6461	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6462	case happyOut305 happy_x_2 of { (HappyWrap305 happy_var_2) ->
6463	case happyOutTok happy_x_3 of { happy_var_3 ->
6464	case happyOut157 happy_x_4 of { (HappyWrap157 happy_var_4) ->
6465	case happyOutTok happy_x_5 of { happy_var_5 ->
6466	( ams (sLL happy_var_1 happy_var_5 (RuleTyTmVar happy_var_2 (Just happy_var_4)))
6467                                               [mop happy_var_1,mu AnnDcolon happy_var_3,mcp happy_var_5])}}}}})
6468	) (\r -> happyReturn (happyIn135 r))
6469
6470happyReduce_308 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6471happyReduce_308 = happyMonadReduce 3# 120# happyReduction_308
6472happyReduction_308 (happy_x_3 `HappyStk`
6473	happy_x_2 `HappyStk`
6474	happy_x_1 `HappyStk`
6475	happyRest) tk
6476	 = happyThen ((case happyOut136 happy_x_1 of { (HappyWrap136 happy_var_1) ->
6477	case happyOutTok happy_x_2 of { happy_var_2 ->
6478	case happyOut137 happy_x_3 of { (HappyWrap137 happy_var_3) ->
6479	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6480                                          >> return (happy_var_1 `appOL` happy_var_3))}}})
6481	) (\r -> happyReturn (happyIn136 r))
6482
6483happyReduce_309 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6484happyReduce_309 = happyMonadReduce 2# 120# happyReduction_309
6485happyReduction_309 (happy_x_2 `HappyStk`
6486	happy_x_1 `HappyStk`
6487	happyRest) tk
6488	 = happyThen ((case happyOut136 happy_x_1 of { (HappyWrap136 happy_var_1) ->
6489	case happyOutTok happy_x_2 of { happy_var_2 ->
6490	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6491                                          >> return happy_var_1)}})
6492	) (\r -> happyReturn (happyIn136 r))
6493
6494happyReduce_310 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6495happyReduce_310 = happySpecReduce_1  120# happyReduction_310
6496happyReduction_310 happy_x_1
6497	 =  case happyOut137 happy_x_1 of { (HappyWrap137 happy_var_1) ->
6498	happyIn136
6499		 (happy_var_1
6500	)}
6501
6502happyReduce_311 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6503happyReduce_311 = happySpecReduce_0  120# happyReduction_311
6504happyReduction_311  =  happyIn136
6505		 (nilOL
6506	)
6507
6508happyReduce_312 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6509happyReduce_312 = happyMonadReduce 2# 121# happyReduction_312
6510happyReduction_312 (happy_x_2 `HappyStk`
6511	happy_x_1 `HappyStk`
6512	happyRest) tk
6513	 = happyThen ((case happyOut271 happy_x_1 of { (HappyWrap271 happy_var_1) ->
6514	case happyOut140 happy_x_2 of { (HappyWrap140 happy_var_2) ->
6515	( amsu (sLL happy_var_1 happy_var_2 (Warning noExtField (unLoc happy_var_1) (WarningTxt (noLoc NoSourceText) $ snd $ unLoc happy_var_2)))
6516                     (fst $ unLoc happy_var_2))}})
6517	) (\r -> happyReturn (happyIn137 r))
6518
6519happyReduce_313 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6520happyReduce_313 = happyMonadReduce 3# 122# happyReduction_313
6521happyReduction_313 (happy_x_3 `HappyStk`
6522	happy_x_2 `HappyStk`
6523	happy_x_1 `HappyStk`
6524	happyRest) tk
6525	 = happyThen ((case happyOut138 happy_x_1 of { (HappyWrap138 happy_var_1) ->
6526	case happyOutTok happy_x_2 of { happy_var_2 ->
6527	case happyOut139 happy_x_3 of { (HappyWrap139 happy_var_3) ->
6528	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6529                                          >> return (happy_var_1 `appOL` happy_var_3))}}})
6530	) (\r -> happyReturn (happyIn138 r))
6531
6532happyReduce_314 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6533happyReduce_314 = happyMonadReduce 2# 122# happyReduction_314
6534happyReduction_314 (happy_x_2 `HappyStk`
6535	happy_x_1 `HappyStk`
6536	happyRest) tk
6537	 = happyThen ((case happyOut138 happy_x_1 of { (HappyWrap138 happy_var_1) ->
6538	case happyOutTok happy_x_2 of { happy_var_2 ->
6539	( addAnnotation (oll happy_var_1) AnnSemi (gl happy_var_2)
6540                                          >> return happy_var_1)}})
6541	) (\r -> happyReturn (happyIn138 r))
6542
6543happyReduce_315 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6544happyReduce_315 = happySpecReduce_1  122# happyReduction_315
6545happyReduction_315 happy_x_1
6546	 =  case happyOut139 happy_x_1 of { (HappyWrap139 happy_var_1) ->
6547	happyIn138
6548		 (happy_var_1
6549	)}
6550
6551happyReduce_316 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6552happyReduce_316 = happySpecReduce_0  122# happyReduction_316
6553happyReduction_316  =  happyIn138
6554		 (nilOL
6555	)
6556
6557happyReduce_317 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6558happyReduce_317 = happyMonadReduce 2# 123# happyReduction_317
6559happyReduction_317 (happy_x_2 `HappyStk`
6560	happy_x_1 `HappyStk`
6561	happyRest) tk
6562	 = happyThen ((case happyOut271 happy_x_1 of { (HappyWrap271 happy_var_1) ->
6563	case happyOut140 happy_x_2 of { (HappyWrap140 happy_var_2) ->
6564	( amsu (sLL happy_var_1 happy_var_2 $ (Warning noExtField (unLoc happy_var_1) (DeprecatedTxt (noLoc NoSourceText) $ snd $ unLoc happy_var_2)))
6565                     (fst $ unLoc happy_var_2))}})
6566	) (\r -> happyReturn (happyIn139 r))
6567
6568happyReduce_318 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6569happyReduce_318 = happySpecReduce_1  124# happyReduction_318
6570happyReduction_318 happy_x_1
6571	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6572	happyIn140
6573		 (sL1 happy_var_1 ([],[cL (gl happy_var_1) (getStringLiteral happy_var_1)])
6574	)}
6575
6576happyReduce_319 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6577happyReduce_319 = happySpecReduce_3  124# happyReduction_319
6578happyReduction_319 happy_x_3
6579	happy_x_2
6580	happy_x_1
6581	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6582	case happyOut141 happy_x_2 of { (HappyWrap141 happy_var_2) ->
6583	case happyOutTok happy_x_3 of { happy_var_3 ->
6584	happyIn140
6585		 (sLL happy_var_1 happy_var_3 $ ([mos happy_var_1,mcs happy_var_3],fromOL (unLoc happy_var_2))
6586	)}}}
6587
6588happyReduce_320 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6589happyReduce_320 = happyMonadReduce 3# 125# happyReduction_320
6590happyReduction_320 (happy_x_3 `HappyStk`
6591	happy_x_2 `HappyStk`
6592	happy_x_1 `HappyStk`
6593	happyRest) tk
6594	 = happyThen ((case happyOut141 happy_x_1 of { (HappyWrap141 happy_var_1) ->
6595	case happyOutTok happy_x_2 of { happy_var_2 ->
6596	case happyOutTok happy_x_3 of { happy_var_3 ->
6597	( addAnnotation (oll $ unLoc happy_var_1) AnnComma (gl happy_var_2) >>
6598                               return (sLL happy_var_1 happy_var_3 (unLoc happy_var_1 `snocOL`
6599                                                  (cL (gl happy_var_3) (getStringLiteral happy_var_3)))))}}})
6600	) (\r -> happyReturn (happyIn141 r))
6601
6602happyReduce_321 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6603happyReduce_321 = happySpecReduce_1  125# happyReduction_321
6604happyReduction_321 happy_x_1
6605	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6606	happyIn141
6607		 (sLL happy_var_1 happy_var_1 (unitOL (cL (gl happy_var_1) (getStringLiteral happy_var_1)))
6608	)}
6609
6610happyReduce_322 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6611happyReduce_322 = happySpecReduce_0  125# happyReduction_322
6612happyReduction_322  =  happyIn141
6613		 (noLoc nilOL
6614	)
6615
6616happyReduce_323 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6617happyReduce_323 = happyMonadReduce 4# 126# happyReduction_323
6618happyReduction_323 (happy_x_4 `HappyStk`
6619	happy_x_3 `HappyStk`
6620	happy_x_2 `HappyStk`
6621	happy_x_1 `HappyStk`
6622	happyRest) tk
6623	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6624	case happyOut272 happy_x_2 of { (HappyWrap272 happy_var_2) ->
6625	case happyOut218 happy_x_3 of { (HappyWrap218 happy_var_3) ->
6626	case happyOutTok happy_x_4 of { happy_var_4 ->
6627	( runECP_P happy_var_3 >>= \ happy_var_3 ->
6628                                            ams (sLL happy_var_1 happy_var_4 (AnnD noExtField $ HsAnnotation noExtField
6629                                            (getANN_PRAGs happy_var_1)
6630                                            (ValueAnnProvenance happy_var_2) happy_var_3))
6631                                            [mo happy_var_1,mc happy_var_4])}}}})
6632	) (\r -> happyReturn (happyIn142 r))
6633
6634happyReduce_324 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6635happyReduce_324 = happyMonadReduce 5# 126# happyReduction_324
6636happyReduction_324 (happy_x_5 `HappyStk`
6637	happy_x_4 `HappyStk`
6638	happy_x_3 `HappyStk`
6639	happy_x_2 `HappyStk`
6640	happy_x_1 `HappyStk`
6641	happyRest) tk
6642	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6643	case happyOutTok happy_x_2 of { happy_var_2 ->
6644	case happyOut289 happy_x_3 of { (HappyWrap289 happy_var_3) ->
6645	case happyOut218 happy_x_4 of { (HappyWrap218 happy_var_4) ->
6646	case happyOutTok happy_x_5 of { happy_var_5 ->
6647	( runECP_P happy_var_4 >>= \ happy_var_4 ->
6648                                            ams (sLL happy_var_1 happy_var_5 (AnnD noExtField $ HsAnnotation noExtField
6649                                            (getANN_PRAGs happy_var_1)
6650                                            (TypeAnnProvenance happy_var_3) happy_var_4))
6651                                            [mo happy_var_1,mj AnnType happy_var_2,mc happy_var_5])}}}}})
6652	) (\r -> happyReturn (happyIn142 r))
6653
6654happyReduce_325 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6655happyReduce_325 = happyMonadReduce 4# 126# happyReduction_325
6656happyReduction_325 (happy_x_4 `HappyStk`
6657	happy_x_3 `HappyStk`
6658	happy_x_2 `HappyStk`
6659	happy_x_1 `HappyStk`
6660	happyRest) tk
6661	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6662	case happyOutTok happy_x_2 of { happy_var_2 ->
6663	case happyOut218 happy_x_3 of { (HappyWrap218 happy_var_3) ->
6664	case happyOutTok happy_x_4 of { happy_var_4 ->
6665	( runECP_P happy_var_3 >>= \ happy_var_3 ->
6666                                            ams (sLL happy_var_1 happy_var_4 (AnnD noExtField $ HsAnnotation noExtField
6667                                                (getANN_PRAGs happy_var_1)
6668                                                 ModuleAnnProvenance happy_var_3))
6669                                                [mo happy_var_1,mj AnnModule happy_var_2,mc happy_var_4])}}}})
6670	) (\r -> happyReturn (happyIn142 r))
6671
6672happyReduce_326 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6673happyReduce_326 = happyMonadReduce 4# 127# happyReduction_326
6674happyReduction_326 (happy_x_4 `HappyStk`
6675	happy_x_3 `HappyStk`
6676	happy_x_2 `HappyStk`
6677	happy_x_1 `HappyStk`
6678	happyRest) tk
6679	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6680	case happyOut144 happy_x_2 of { (HappyWrap144 happy_var_2) ->
6681	case happyOut145 happy_x_3 of { (HappyWrap145 happy_var_3) ->
6682	case happyOut146 happy_x_4 of { (HappyWrap146 happy_var_4) ->
6683	( mkImport happy_var_2 happy_var_3 (snd $ unLoc happy_var_4) >>= \i ->
6684                 return (sLL happy_var_1 happy_var_4 (mj AnnImport happy_var_1 : (fst $ unLoc happy_var_4),i)))}}}})
6685	) (\r -> happyReturn (happyIn143 r))
6686
6687happyReduce_327 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6688happyReduce_327 = happyMonadReduce 3# 127# happyReduction_327
6689happyReduction_327 (happy_x_3 `HappyStk`
6690	happy_x_2 `HappyStk`
6691	happy_x_1 `HappyStk`
6692	happyRest) tk
6693	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6694	case happyOut144 happy_x_2 of { (HappyWrap144 happy_var_2) ->
6695	case happyOut146 happy_x_3 of { (HappyWrap146 happy_var_3) ->
6696	( do { d <- mkImport happy_var_2 (noLoc PlaySafe) (snd $ unLoc happy_var_3);
6697                    return (sLL happy_var_1 happy_var_3 (mj AnnImport happy_var_1 : (fst $ unLoc happy_var_3),d)) })}}})
6698	) (\r -> happyReturn (happyIn143 r))
6699
6700happyReduce_328 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6701happyReduce_328 = happyMonadReduce 3# 127# happyReduction_328
6702happyReduction_328 (happy_x_3 `HappyStk`
6703	happy_x_2 `HappyStk`
6704	happy_x_1 `HappyStk`
6705	happyRest) tk
6706	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6707	case happyOut144 happy_x_2 of { (HappyWrap144 happy_var_2) ->
6708	case happyOut146 happy_x_3 of { (HappyWrap146 happy_var_3) ->
6709	( mkExport happy_var_2 (snd $ unLoc happy_var_3) >>= \i ->
6710                  return (sLL happy_var_1 happy_var_3 (mj AnnExport happy_var_1 : (fst $ unLoc happy_var_3),i) ))}}})
6711	) (\r -> happyReturn (happyIn143 r))
6712
6713happyReduce_329 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6714happyReduce_329 = happySpecReduce_1  128# happyReduction_329
6715happyReduction_329 happy_x_1
6716	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6717	happyIn144
6718		 (sLL happy_var_1 happy_var_1 StdCallConv
6719	)}
6720
6721happyReduce_330 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6722happyReduce_330 = happySpecReduce_1  128# happyReduction_330
6723happyReduction_330 happy_x_1
6724	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6725	happyIn144
6726		 (sLL happy_var_1 happy_var_1 CCallConv
6727	)}
6728
6729happyReduce_331 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6730happyReduce_331 = happySpecReduce_1  128# happyReduction_331
6731happyReduction_331 happy_x_1
6732	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6733	happyIn144
6734		 (sLL happy_var_1 happy_var_1 CApiConv
6735	)}
6736
6737happyReduce_332 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6738happyReduce_332 = happySpecReduce_1  128# happyReduction_332
6739happyReduction_332 happy_x_1
6740	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6741	happyIn144
6742		 (sLL happy_var_1 happy_var_1 PrimCallConv
6743	)}
6744
6745happyReduce_333 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6746happyReduce_333 = happySpecReduce_1  128# happyReduction_333
6747happyReduction_333 happy_x_1
6748	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6749	happyIn144
6750		 (sLL happy_var_1 happy_var_1 JavaScriptCallConv
6751	)}
6752
6753happyReduce_334 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6754happyReduce_334 = happySpecReduce_1  129# happyReduction_334
6755happyReduction_334 happy_x_1
6756	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6757	happyIn145
6758		 (sLL happy_var_1 happy_var_1 PlayRisky
6759	)}
6760
6761happyReduce_335 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6762happyReduce_335 = happySpecReduce_1  129# happyReduction_335
6763happyReduction_335 happy_x_1
6764	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6765	happyIn145
6766		 (sLL happy_var_1 happy_var_1 PlaySafe
6767	)}
6768
6769happyReduce_336 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6770happyReduce_336 = happySpecReduce_1  129# happyReduction_336
6771happyReduction_336 happy_x_1
6772	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6773	happyIn145
6774		 (sLL happy_var_1 happy_var_1 PlayInterruptible
6775	)}
6776
6777happyReduce_337 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6778happyReduce_337 = happyReduce 4# 130# happyReduction_337
6779happyReduction_337 (happy_x_4 `HappyStk`
6780	happy_x_3 `HappyStk`
6781	happy_x_2 `HappyStk`
6782	happy_x_1 `HappyStk`
6783	happyRest)
6784	 = case happyOutTok happy_x_1 of { happy_var_1 ->
6785	case happyOut302 happy_x_2 of { (HappyWrap302 happy_var_2) ->
6786	case happyOutTok happy_x_3 of { happy_var_3 ->
6787	case happyOut150 happy_x_4 of { (HappyWrap150 happy_var_4) ->
6788	happyIn146
6789		 (sLL happy_var_1 happy_var_4 ([mu AnnDcolon happy_var_3]
6790                                             ,(cL (getLoc happy_var_1)
6791                                                    (getStringLiteral happy_var_1), happy_var_2, mkLHsSigType happy_var_4))
6792	) `HappyStk` happyRest}}}}
6793
6794happyReduce_338 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6795happyReduce_338 = happySpecReduce_3  130# happyReduction_338
6796happyReduction_338 happy_x_3
6797	happy_x_2
6798	happy_x_1
6799	 =  case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
6800	case happyOutTok happy_x_2 of { happy_var_2 ->
6801	case happyOut150 happy_x_3 of { (HappyWrap150 happy_var_3) ->
6802	happyIn146
6803		 (sLL happy_var_1 happy_var_3 ([mu AnnDcolon happy_var_2]
6804                                             ,(noLoc (StringLiteral NoSourceText nilFS), happy_var_1, mkLHsSigType happy_var_3))
6805	)}}}
6806
6807happyReduce_339 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6808happyReduce_339 = happySpecReduce_0  131# happyReduction_339
6809happyReduction_339  =  happyIn147
6810		 (([],Nothing)
6811	)
6812
6813happyReduce_340 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6814happyReduce_340 = happySpecReduce_2  131# happyReduction_340
6815happyReduction_340 happy_x_2
6816	happy_x_1
6817	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6818	case happyOut149 happy_x_2 of { (HappyWrap149 happy_var_2) ->
6819	happyIn147
6820		 (([mu AnnDcolon happy_var_1],Just happy_var_2)
6821	)}}
6822
6823happyReduce_341 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6824happyReduce_341 = happySpecReduce_0  132# happyReduction_341
6825happyReduction_341  =  happyIn148
6826		 (([], Nothing)
6827	)
6828
6829happyReduce_342 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6830happyReduce_342 = happySpecReduce_2  132# happyReduction_342
6831happyReduction_342 happy_x_2
6832	happy_x_1
6833	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6834	case happyOut282 happy_x_2 of { (HappyWrap282 happy_var_2) ->
6835	happyIn148
6836		 (([mu AnnDcolon happy_var_1], Just happy_var_2)
6837	)}}
6838
6839happyReduce_343 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6840happyReduce_343 = happySpecReduce_1  133# happyReduction_343
6841happyReduction_343 happy_x_1
6842	 =  case happyOut157 happy_x_1 of { (HappyWrap157 happy_var_1) ->
6843	happyIn149
6844		 (happy_var_1
6845	)}
6846
6847happyReduce_344 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6848happyReduce_344 = happySpecReduce_1  134# happyReduction_344
6849happyReduction_344 happy_x_1
6850	 =  case happyOut158 happy_x_1 of { (HappyWrap158 happy_var_1) ->
6851	happyIn150
6852		 (happy_var_1
6853	)}
6854
6855happyReduce_345 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6856happyReduce_345 = happyMonadReduce 3# 135# happyReduction_345
6857happyReduction_345 (happy_x_3 `HappyStk`
6858	happy_x_2 `HappyStk`
6859	happy_x_1 `HappyStk`
6860	happyRest) tk
6861	 = happyThen ((case happyOut151 happy_x_1 of { (HappyWrap151 happy_var_1) ->
6862	case happyOutTok happy_x_2 of { happy_var_2 ->
6863	case happyOut302 happy_x_3 of { (HappyWrap302 happy_var_3) ->
6864	( addAnnotation (gl $ head $ unLoc happy_var_1)
6865                                                       AnnComma (gl happy_var_2)
6866                                         >> return (sLL happy_var_1 happy_var_3 (happy_var_3 : unLoc happy_var_1)))}}})
6867	) (\r -> happyReturn (happyIn151 r))
6868
6869happyReduce_346 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6870happyReduce_346 = happySpecReduce_1  135# happyReduction_346
6871happyReduction_346 happy_x_1
6872	 =  case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
6873	happyIn151
6874		 (sL1 happy_var_1 [happy_var_1]
6875	)}
6876
6877happyReduce_347 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6878happyReduce_347 = happySpecReduce_1  136# happyReduction_347
6879happyReduction_347 happy_x_1
6880	 =  case happyOut149 happy_x_1 of { (HappyWrap149 happy_var_1) ->
6881	happyIn152
6882		 (unitOL (mkLHsSigType happy_var_1)
6883	)}
6884
6885happyReduce_348 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6886happyReduce_348 = happyMonadReduce 3# 136# happyReduction_348
6887happyReduction_348 (happy_x_3 `HappyStk`
6888	happy_x_2 `HappyStk`
6889	happy_x_1 `HappyStk`
6890	happyRest) tk
6891	 = happyThen ((case happyOut149 happy_x_1 of { (HappyWrap149 happy_var_1) ->
6892	case happyOutTok happy_x_2 of { happy_var_2 ->
6893	case happyOut152 happy_x_3 of { (HappyWrap152 happy_var_3) ->
6894	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2)
6895                                >> return (unitOL (mkLHsSigType happy_var_1) `appOL` happy_var_3))}}})
6896	) (\r -> happyReturn (happyIn152 r))
6897
6898happyReduce_349 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6899happyReduce_349 = happySpecReduce_2  137# happyReduction_349
6900happyReduction_349 happy_x_2
6901	happy_x_1
6902	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6903	case happyOutTok happy_x_2 of { happy_var_2 ->
6904	happyIn153
6905		 (sLL happy_var_1 happy_var_2 ([mo happy_var_1, mc happy_var_2], getUNPACK_PRAGs happy_var_1, SrcUnpack)
6906	)}}
6907
6908happyReduce_350 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6909happyReduce_350 = happySpecReduce_2  137# happyReduction_350
6910happyReduction_350 happy_x_2
6911	happy_x_1
6912	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6913	case happyOutTok happy_x_2 of { happy_var_2 ->
6914	happyIn153
6915		 (sLL happy_var_1 happy_var_2 ([mo happy_var_1, mc happy_var_2], getNOUNPACK_PRAGs happy_var_1, SrcNoUnpack)
6916	)}}
6917
6918happyReduce_351 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6919happyReduce_351 = happySpecReduce_1  138# happyReduction_351
6920happyReduction_351 happy_x_1
6921	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6922	happyIn154
6923		 ((mj AnnDot happy_var_1,    ForallInvis)
6924	)}
6925
6926happyReduce_352 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6927happyReduce_352 = happySpecReduce_1  138# happyReduction_352
6928happyReduction_352 happy_x_1
6929	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
6930	happyIn154
6931		 ((mu AnnRarrow happy_var_1, ForallVis)
6932	)}
6933
6934happyReduce_353 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6935happyReduce_353 = happySpecReduce_1  139# happyReduction_353
6936happyReduction_353 happy_x_1
6937	 =  case happyOut157 happy_x_1 of { (HappyWrap157 happy_var_1) ->
6938	happyIn155
6939		 (happy_var_1
6940	)}
6941
6942happyReduce_354 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6943happyReduce_354 = happyMonadReduce 3# 139# happyReduction_354
6944happyReduction_354 (happy_x_3 `HappyStk`
6945	happy_x_2 `HappyStk`
6946	happy_x_1 `HappyStk`
6947	happyRest) tk
6948	 = happyThen ((case happyOut157 happy_x_1 of { (HappyWrap157 happy_var_1) ->
6949	case happyOutTok happy_x_2 of { happy_var_2 ->
6950	case happyOut181 happy_x_3 of { (HappyWrap181 happy_var_3) ->
6951	( ams (sLL happy_var_1 happy_var_3 $ HsKindSig noExtField happy_var_1 happy_var_3)
6952                                      [mu AnnDcolon happy_var_2])}}})
6953	) (\r -> happyReturn (happyIn155 r))
6954
6955happyReduce_355 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6956happyReduce_355 = happySpecReduce_1  140# happyReduction_355
6957happyReduction_355 happy_x_1
6958	 =  case happyOut158 happy_x_1 of { (HappyWrap158 happy_var_1) ->
6959	happyIn156
6960		 (happy_var_1
6961	)}
6962
6963happyReduce_356 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6964happyReduce_356 = happyMonadReduce 3# 140# happyReduction_356
6965happyReduction_356 (happy_x_3 `HappyStk`
6966	happy_x_2 `HappyStk`
6967	happy_x_1 `HappyStk`
6968	happyRest) tk
6969	 = happyThen ((case happyOut158 happy_x_1 of { (HappyWrap158 happy_var_1) ->
6970	case happyOutTok happy_x_2 of { happy_var_2 ->
6971	case happyOut181 happy_x_3 of { (HappyWrap181 happy_var_3) ->
6972	( ams (sLL happy_var_1 happy_var_3 $ HsKindSig noExtField happy_var_1 happy_var_3)
6973                                      [mu AnnDcolon happy_var_2])}}})
6974	) (\r -> happyReturn (happyIn156 r))
6975
6976happyReduce_357 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6977happyReduce_357 = happyMonadReduce 4# 141# happyReduction_357
6978happyReduction_357 (happy_x_4 `HappyStk`
6979	happy_x_3 `HappyStk`
6980	happy_x_2 `HappyStk`
6981	happy_x_1 `HappyStk`
6982	happyRest) tk
6983	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
6984	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
6985	case happyOut154 happy_x_3 of { (HappyWrap154 happy_var_3) ->
6986	case happyOut157 happy_x_4 of { (HappyWrap157 happy_var_4) ->
6987	( let (fv_ann, fv_flag) = happy_var_3 in
6988                                           hintExplicitForall happy_var_1 *>
6989                                           ams (sLL happy_var_1 happy_var_4 $
6990                                                HsForAllTy { hst_fvf = fv_flag
6991                                                           , hst_bndrs = happy_var_2
6992                                                           , hst_xforall = noExtField
6993                                                           , hst_body = happy_var_4 })
6994                                               [mu AnnForall happy_var_1,fv_ann])}}}})
6995	) (\r -> happyReturn (happyIn157 r))
6996
6997happyReduce_358 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
6998happyReduce_358 = happyMonadReduce 3# 141# happyReduction_358
6999happyReduction_358 (happy_x_3 `HappyStk`
7000	happy_x_2 `HappyStk`
7001	happy_x_1 `HappyStk`
7002	happyRest) tk
7003	 = happyThen ((case happyOut159 happy_x_1 of { (HappyWrap159 happy_var_1) ->
7004	case happyOutTok happy_x_2 of { happy_var_2 ->
7005	case happyOut157 happy_x_3 of { (HappyWrap157 happy_var_3) ->
7006	( addAnnotation (gl happy_var_1) (toUnicodeAnn AnnDarrow happy_var_2) (gl happy_var_2)
7007                                         >> return (sLL happy_var_1 happy_var_3 $
7008                                            HsQualTy { hst_ctxt = happy_var_1
7009                                                     , hst_xqual = noExtField
7010                                                     , hst_body = happy_var_3 }))}}})
7011	) (\r -> happyReturn (happyIn157 r))
7012
7013happyReduce_359 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7014happyReduce_359 = happyMonadReduce 3# 141# happyReduction_359
7015happyReduction_359 (happy_x_3 `HappyStk`
7016	happy_x_2 `HappyStk`
7017	happy_x_1 `HappyStk`
7018	happyRest) tk
7019	 = happyThen ((case happyOut264 happy_x_1 of { (HappyWrap264 happy_var_1) ->
7020	case happyOutTok happy_x_2 of { happy_var_2 ->
7021	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
7022	( ams (sLL happy_var_1 happy_var_3 (HsIParamTy noExtField happy_var_1 happy_var_3))
7023                                             [mu AnnDcolon happy_var_2])}}})
7024	) (\r -> happyReturn (happyIn157 r))
7025
7026happyReduce_360 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7027happyReduce_360 = happySpecReduce_1  141# happyReduction_360
7028happyReduction_360 happy_x_1
7029	 =  case happyOut161 happy_x_1 of { (HappyWrap161 happy_var_1) ->
7030	happyIn157
7031		 (happy_var_1
7032	)}
7033
7034happyReduce_361 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7035happyReduce_361 = happyMonadReduce 4# 142# happyReduction_361
7036happyReduction_361 (happy_x_4 `HappyStk`
7037	happy_x_3 `HappyStk`
7038	happy_x_2 `HappyStk`
7039	happy_x_1 `HappyStk`
7040	happyRest) tk
7041	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7042	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
7043	case happyOut154 happy_x_3 of { (HappyWrap154 happy_var_3) ->
7044	case happyOut158 happy_x_4 of { (HappyWrap158 happy_var_4) ->
7045	( let (fv_ann, fv_flag) = happy_var_3 in
7046                                            hintExplicitForall happy_var_1 *>
7047                                            ams (sLL happy_var_1 happy_var_4 $
7048                                                 HsForAllTy { hst_fvf = fv_flag
7049                                                            , hst_bndrs = happy_var_2
7050                                                            , hst_xforall = noExtField
7051                                                            , hst_body = happy_var_4 })
7052                                                [mu AnnForall happy_var_1,fv_ann])}}}})
7053	) (\r -> happyReturn (happyIn158 r))
7054
7055happyReduce_362 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7056happyReduce_362 = happyMonadReduce 3# 142# happyReduction_362
7057happyReduction_362 (happy_x_3 `HappyStk`
7058	happy_x_2 `HappyStk`
7059	happy_x_1 `HappyStk`
7060	happyRest) tk
7061	 = happyThen ((case happyOut159 happy_x_1 of { (HappyWrap159 happy_var_1) ->
7062	case happyOutTok happy_x_2 of { happy_var_2 ->
7063	case happyOut158 happy_x_3 of { (HappyWrap158 happy_var_3) ->
7064	( addAnnotation (gl happy_var_1) (toUnicodeAnn AnnDarrow happy_var_2) (gl happy_var_2)
7065                                         >> return (sLL happy_var_1 happy_var_3 $
7066                                            HsQualTy { hst_ctxt = happy_var_1
7067                                                     , hst_xqual = noExtField
7068                                                     , hst_body = happy_var_3 }))}}})
7069	) (\r -> happyReturn (happyIn158 r))
7070
7071happyReduce_363 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7072happyReduce_363 = happyMonadReduce 3# 142# happyReduction_363
7073happyReduction_363 (happy_x_3 `HappyStk`
7074	happy_x_2 `HappyStk`
7075	happy_x_1 `HappyStk`
7076	happyRest) tk
7077	 = happyThen ((case happyOut264 happy_x_1 of { (HappyWrap264 happy_var_1) ->
7078	case happyOutTok happy_x_2 of { happy_var_2 ->
7079	case happyOut161 happy_x_3 of { (HappyWrap161 happy_var_3) ->
7080	( ams (sLL happy_var_1 happy_var_3 (HsIParamTy noExtField happy_var_1 happy_var_3))
7081                                             [mu AnnDcolon happy_var_2])}}})
7082	) (\r -> happyReturn (happyIn158 r))
7083
7084happyReduce_364 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7085happyReduce_364 = happySpecReduce_1  142# happyReduction_364
7086happyReduction_364 happy_x_1
7087	 =  case happyOut162 happy_x_1 of { (HappyWrap162 happy_var_1) ->
7088	happyIn158
7089		 (happy_var_1
7090	)}
7091
7092happyReduce_365 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7093happyReduce_365 = happyMonadReduce 1# 143# happyReduction_365
7094happyReduction_365 (happy_x_1 `HappyStk`
7095	happyRest) tk
7096	 = happyThen ((case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7097	( do { (anns,ctx) <- checkContext happy_var_1
7098                                                ; if null (unLoc ctx)
7099                                                   then addAnnotation (gl happy_var_1) AnnUnit (gl happy_var_1)
7100                                                   else return ()
7101                                                ; ams ctx anns
7102                                                })})
7103	) (\r -> happyReturn (happyIn159 r))
7104
7105happyReduce_366 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7106happyReduce_366 = happyMonadReduce 1# 144# happyReduction_366
7107happyReduction_366 (happy_x_1 `HappyStk`
7108	happyRest) tk
7109	 = happyThen ((case happyOut163 happy_x_1 of { (HappyWrap163 happy_var_1) ->
7110	( do { (anns,ctx) <- checkContext happy_var_1
7111                                                ; if null (unLoc ctx)
7112                                                   then addAnnotation (gl happy_var_1) AnnUnit (gl happy_var_1)
7113                                                   else return ()
7114                                                ; ams ctx anns
7115                                                })})
7116	) (\r -> happyReturn (happyIn160 r))
7117
7118happyReduce_367 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7119happyReduce_367 = happySpecReduce_1  145# happyReduction_367
7120happyReduction_367 happy_x_1
7121	 =  case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7122	happyIn161
7123		 (happy_var_1
7124	)}
7125
7126happyReduce_368 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7127happyReduce_368 = happyMonadReduce 3# 145# happyReduction_368
7128happyReduction_368 (happy_x_3 `HappyStk`
7129	happy_x_2 `HappyStk`
7130	happy_x_1 `HappyStk`
7131	happyRest) tk
7132	 = happyThen ((case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7133	case happyOutTok happy_x_2 of { happy_var_2 ->
7134	case happyOut157 happy_x_3 of { (HappyWrap157 happy_var_3) ->
7135	( ams happy_var_1 [mu AnnRarrow happy_var_2] -- See note [GADT decl discards annotations]
7136                                       >> ams (sLL happy_var_1 happy_var_3 $ HsFunTy noExtField happy_var_1 happy_var_3)
7137                                              [mu AnnRarrow happy_var_2])}}})
7138	) (\r -> happyReturn (happyIn161 r))
7139
7140happyReduce_369 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7141happyReduce_369 = happySpecReduce_1  146# happyReduction_369
7142happyReduction_369 happy_x_1
7143	 =  case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7144	happyIn162
7145		 (happy_var_1
7146	)}
7147
7148happyReduce_370 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7149happyReduce_370 = happySpecReduce_2  146# happyReduction_370
7150happyReduction_370 happy_x_2
7151	happy_x_1
7152	 =  case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7153	case happyOut324 happy_x_2 of { (HappyWrap324 happy_var_2) ->
7154	happyIn162
7155		 (sLL happy_var_1 happy_var_2 $ HsDocTy noExtField happy_var_1 happy_var_2
7156	)}}
7157
7158happyReduce_371 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7159happyReduce_371 = happySpecReduce_2  146# happyReduction_371
7160happyReduction_371 happy_x_2
7161	happy_x_1
7162	 =  case happyOut323 happy_x_1 of { (HappyWrap323 happy_var_1) ->
7163	case happyOut166 happy_x_2 of { (HappyWrap166 happy_var_2) ->
7164	happyIn162
7165		 (sLL happy_var_1 happy_var_2 $ HsDocTy noExtField happy_var_2 happy_var_1
7166	)}}
7167
7168happyReduce_372 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7169happyReduce_372 = happyMonadReduce 3# 146# happyReduction_372
7170happyReduction_372 (happy_x_3 `HappyStk`
7171	happy_x_2 `HappyStk`
7172	happy_x_1 `HappyStk`
7173	happyRest) tk
7174	 = happyThen ((case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7175	case happyOutTok happy_x_2 of { happy_var_2 ->
7176	case happyOut158 happy_x_3 of { (HappyWrap158 happy_var_3) ->
7177	( ams happy_var_1 [mu AnnRarrow happy_var_2] -- See note [GADT decl discards annotations]
7178                                         >> ams (sLL happy_var_1 happy_var_3 $ HsFunTy noExtField happy_var_1 happy_var_3)
7179                                                [mu AnnRarrow happy_var_2])}}})
7180	) (\r -> happyReturn (happyIn162 r))
7181
7182happyReduce_373 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7183happyReduce_373 = happyMonadReduce 4# 146# happyReduction_373
7184happyReduction_373 (happy_x_4 `HappyStk`
7185	happy_x_3 `HappyStk`
7186	happy_x_2 `HappyStk`
7187	happy_x_1 `HappyStk`
7188	happyRest) tk
7189	 = happyThen ((case happyOut166 happy_x_1 of { (HappyWrap166 happy_var_1) ->
7190	case happyOut324 happy_x_2 of { (HappyWrap324 happy_var_2) ->
7191	case happyOutTok happy_x_3 of { happy_var_3 ->
7192	case happyOut158 happy_x_4 of { (HappyWrap158 happy_var_4) ->
7193	( ams happy_var_1 [mu AnnRarrow happy_var_3] -- See note [GADT decl discards annotations]
7194                                         >> ams (sLL happy_var_1 happy_var_4 $
7195                                                 HsFunTy noExtField (cL (comb2 happy_var_1 happy_var_2)
7196                                                            (HsDocTy noExtField happy_var_1 happy_var_2))
7197                                                         happy_var_4)
7198                                                [mu AnnRarrow happy_var_3])}}}})
7199	) (\r -> happyReturn (happyIn162 r))
7200
7201happyReduce_374 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7202happyReduce_374 = happyMonadReduce 4# 146# happyReduction_374
7203happyReduction_374 (happy_x_4 `HappyStk`
7204	happy_x_3 `HappyStk`
7205	happy_x_2 `HappyStk`
7206	happy_x_1 `HappyStk`
7207	happyRest) tk
7208	 = happyThen ((case happyOut323 happy_x_1 of { (HappyWrap323 happy_var_1) ->
7209	case happyOut166 happy_x_2 of { (HappyWrap166 happy_var_2) ->
7210	case happyOutTok happy_x_3 of { happy_var_3 ->
7211	case happyOut158 happy_x_4 of { (HappyWrap158 happy_var_4) ->
7212	( ams happy_var_2 [mu AnnRarrow happy_var_3] -- See note [GADT decl discards annotations]
7213                                         >> ams (sLL happy_var_1 happy_var_4 $
7214                                                 HsFunTy noExtField (cL (comb2 happy_var_1 happy_var_2)
7215                                                            (HsDocTy noExtField happy_var_2 happy_var_1))
7216                                                         happy_var_4)
7217                                                [mu AnnRarrow happy_var_3])}}}})
7218	) (\r -> happyReturn (happyIn162 r))
7219
7220happyReduce_375 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7221happyReduce_375 = happyMonadReduce 1# 147# happyReduction_375
7222happyReduction_375 (happy_x_1 `HappyStk`
7223	happyRest) tk
7224	 = happyThen ((case happyOut164 happy_x_1 of { (HappyWrap164 happy_var_1) ->
7225	( mergeOps (unLoc happy_var_1))})
7226	) (\r -> happyReturn (happyIn163 r))
7227
7228happyReduce_376 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7229happyReduce_376 = happySpecReduce_1  148# happyReduction_376
7230happyReduction_376 happy_x_1
7231	 =  case happyOut165 happy_x_1 of { (HappyWrap165 happy_var_1) ->
7232	happyIn164
7233		 (sL1 happy_var_1 [happy_var_1]
7234	)}
7235
7236happyReduce_377 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7237happyReduce_377 = happySpecReduce_2  148# happyReduction_377
7238happyReduction_377 happy_x_2
7239	happy_x_1
7240	 =  case happyOut164 happy_x_1 of { (HappyWrap164 happy_var_1) ->
7241	case happyOut165 happy_x_2 of { (HappyWrap165 happy_var_2) ->
7242	happyIn164
7243		 (sLL happy_var_1 happy_var_2 $ happy_var_2 : (unLoc happy_var_1)
7244	)}}
7245
7246happyReduce_378 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7247happyReduce_378 = happySpecReduce_1  149# happyReduction_378
7248happyReduction_378 happy_x_1
7249	 =  case happyOut168 happy_x_1 of { (HappyWrap168 happy_var_1) ->
7250	happyIn165
7251		 (happy_var_1
7252	)}
7253
7254happyReduce_379 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7255happyReduce_379 = happySpecReduce_1  149# happyReduction_379
7256happyReduction_379 happy_x_1
7257	 =  case happyOut324 happy_x_1 of { (HappyWrap324 happy_var_1) ->
7258	happyIn165
7259		 (sL1 happy_var_1 $ TyElDocPrev (unLoc happy_var_1)
7260	)}
7261
7262happyReduce_380 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7263happyReduce_380 = happyMonadReduce 1# 150# happyReduction_380
7264happyReduction_380 (happy_x_1 `HappyStk`
7265	happyRest) tk
7266	 = happyThen ((case happyOut167 happy_x_1 of { (HappyWrap167 happy_var_1) ->
7267	( mergeOps happy_var_1)})
7268	) (\r -> happyReturn (happyIn166 r))
7269
7270happyReduce_381 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7271happyReduce_381 = happySpecReduce_1  151# happyReduction_381
7272happyReduction_381 happy_x_1
7273	 =  case happyOut168 happy_x_1 of { (HappyWrap168 happy_var_1) ->
7274	happyIn167
7275		 ([happy_var_1]
7276	)}
7277
7278happyReduce_382 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7279happyReduce_382 = happySpecReduce_2  151# happyReduction_382
7280happyReduction_382 happy_x_2
7281	happy_x_1
7282	 =  case happyOut167 happy_x_1 of { (HappyWrap167 happy_var_1) ->
7283	case happyOut168 happy_x_2 of { (HappyWrap168 happy_var_2) ->
7284	happyIn167
7285		 (happy_var_2 : happy_var_1
7286	)}}
7287
7288happyReduce_383 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7289happyReduce_383 = happySpecReduce_1  152# happyReduction_383
7290happyReduction_383 happy_x_1
7291	 =  case happyOut169 happy_x_1 of { (HappyWrap169 happy_var_1) ->
7292	happyIn168
7293		 (sL1 happy_var_1 $ TyElOpd (unLoc happy_var_1)
7294	)}
7295
7296happyReduce_384 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7297happyReduce_384 = happySpecReduce_2  152# happyReduction_384
7298happyReduction_384 happy_x_2
7299	happy_x_1
7300	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7301	case happyOut169 happy_x_2 of { (HappyWrap169 happy_var_2) ->
7302	happyIn168
7303		 (sLL happy_var_1 happy_var_2 $ (TyElKindApp (comb2 happy_var_1 happy_var_2) happy_var_2)
7304	)}}
7305
7306happyReduce_385 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7307happyReduce_385 = happySpecReduce_1  152# happyReduction_385
7308happyReduction_385 happy_x_1
7309	 =  case happyOut286 happy_x_1 of { (HappyWrap286 happy_var_1) ->
7310	happyIn168
7311		 (sL1 happy_var_1 $ if isBangRdr (unLoc happy_var_1) then TyElBang else
7312                                                   if isTildeRdr (unLoc happy_var_1) then TyElTilde else
7313                                                   TyElOpr (unLoc happy_var_1)
7314	)}
7315
7316happyReduce_386 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7317happyReduce_386 = happySpecReduce_1  152# happyReduction_386
7318happyReduction_386 happy_x_1
7319	 =  case happyOut300 happy_x_1 of { (HappyWrap300 happy_var_1) ->
7320	happyIn168
7321		 (sL1 happy_var_1 $ TyElOpr (unLoc happy_var_1)
7322	)}
7323
7324happyReduce_387 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7325happyReduce_387 = happyMonadReduce 2# 152# happyReduction_387
7326happyReduction_387 (happy_x_2 `HappyStk`
7327	happy_x_1 `HappyStk`
7328	happyRest) tk
7329	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7330	case happyOut281 happy_x_2 of { (HappyWrap281 happy_var_2) ->
7331	( ams (sLL happy_var_1 happy_var_2 $ TyElOpr (unLoc happy_var_2))
7332                                               [mj AnnSimpleQuote happy_var_1,mj AnnVal happy_var_2])}})
7333	) (\r -> happyReturn (happyIn168 r))
7334
7335happyReduce_388 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7336happyReduce_388 = happyMonadReduce 2# 152# happyReduction_388
7337happyReduction_388 (happy_x_2 `HappyStk`
7338	happy_x_1 `HappyStk`
7339	happyRest) tk
7340	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7341	case happyOut293 happy_x_2 of { (HappyWrap293 happy_var_2) ->
7342	( ams (sLL happy_var_1 happy_var_2 $ TyElOpr (unLoc happy_var_2))
7343                                               [mj AnnSimpleQuote happy_var_1,mj AnnVal happy_var_2])}})
7344	) (\r -> happyReturn (happyIn168 r))
7345
7346happyReduce_389 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7347happyReduce_389 = happySpecReduce_1  152# happyReduction_389
7348happyReduction_389 happy_x_1
7349	 =  case happyOut153 happy_x_1 of { (HappyWrap153 happy_var_1) ->
7350	happyIn168
7351		 (sL1 happy_var_1 $ TyElUnpackedness (unLoc happy_var_1)
7352	)}
7353
7354happyReduce_390 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7355happyReduce_390 = happySpecReduce_1  153# happyReduction_390
7356happyReduction_390 happy_x_1
7357	 =  case happyOut283 happy_x_1 of { (HappyWrap283 happy_var_1) ->
7358	happyIn169
7359		 (sL1 happy_var_1 (HsTyVar noExtField NotPromoted happy_var_1)
7360	)}
7361
7362happyReduce_391 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7363happyReduce_391 = happySpecReduce_1  153# happyReduction_391
7364happyReduction_391 happy_x_1
7365	 =  case happyOut299 happy_x_1 of { (HappyWrap299 happy_var_1) ->
7366	happyIn169
7367		 (sL1 happy_var_1 (HsTyVar noExtField NotPromoted happy_var_1)
7368	)}
7369
7370happyReduce_392 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7371happyReduce_392 = happyMonadReduce 1# 153# happyReduction_392
7372happyReduction_392 (happy_x_1 `HappyStk`
7373	happyRest) tk
7374	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7375	( do { warnStarIsType (getLoc happy_var_1)
7376                                               ; return $ sL1 happy_var_1 (HsStarTy noExtField (isUnicode happy_var_1)) })})
7377	) (\r -> happyReturn (happyIn169 r))
7378
7379happyReduce_393 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7380happyReduce_393 = happyMonadReduce 3# 153# happyReduction_393
7381happyReduction_393 (happy_x_3 `HappyStk`
7382	happy_x_2 `HappyStk`
7383	happy_x_1 `HappyStk`
7384	happyRest) tk
7385	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7386	case happyOut191 happy_x_2 of { (HappyWrap191 happy_var_2) ->
7387	case happyOutTok happy_x_3 of { happy_var_3 ->
7388	( amms (checkRecordSyntax
7389                                                    (sLL happy_var_1 happy_var_3 $ HsRecTy noExtField happy_var_2))
7390                                                        -- Constructor sigs only
7391                                                 [moc happy_var_1,mcc happy_var_3])}}})
7392	) (\r -> happyReturn (happyIn169 r))
7393
7394happyReduce_394 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7395happyReduce_394 = happyMonadReduce 2# 153# happyReduction_394
7396happyReduction_394 (happy_x_2 `HappyStk`
7397	happy_x_1 `HappyStk`
7398	happyRest) tk
7399	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7400	case happyOutTok happy_x_2 of { happy_var_2 ->
7401	( ams (sLL happy_var_1 happy_var_2 $ HsTupleTy noExtField
7402                                                    HsBoxedOrConstraintTuple [])
7403                                                [mop happy_var_1,mcp happy_var_2])}})
7404	) (\r -> happyReturn (happyIn169 r))
7405
7406happyReduce_395 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7407happyReduce_395 = happyMonadReduce 5# 153# happyReduction_395
7408happyReduction_395 (happy_x_5 `HappyStk`
7409	happy_x_4 `HappyStk`
7410	happy_x_3 `HappyStk`
7411	happy_x_2 `HappyStk`
7412	happy_x_1 `HappyStk`
7413	happyRest) tk
7414	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7415	case happyOut155 happy_x_2 of { (HappyWrap155 happy_var_2) ->
7416	case happyOutTok happy_x_3 of { happy_var_3 ->
7417	case happyOut173 happy_x_4 of { (HappyWrap173 happy_var_4) ->
7418	case happyOutTok happy_x_5 of { happy_var_5 ->
7419	( addAnnotation (gl happy_var_2) AnnComma
7420                                                          (gl happy_var_3) >>
7421                                            ams (sLL happy_var_1 happy_var_5 $ HsTupleTy noExtField
7422
7423                                             HsBoxedOrConstraintTuple (happy_var_2 : happy_var_4))
7424                                                [mop happy_var_1,mcp happy_var_5])}}}}})
7425	) (\r -> happyReturn (happyIn169 r))
7426
7427happyReduce_396 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7428happyReduce_396 = happyMonadReduce 2# 153# happyReduction_396
7429happyReduction_396 (happy_x_2 `HappyStk`
7430	happy_x_1 `HappyStk`
7431	happyRest) tk
7432	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7433	case happyOutTok happy_x_2 of { happy_var_2 ->
7434	( ams (sLL happy_var_1 happy_var_2 $ HsTupleTy noExtField HsUnboxedTuple [])
7435                                             [mo happy_var_1,mc happy_var_2])}})
7436	) (\r -> happyReturn (happyIn169 r))
7437
7438happyReduce_397 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7439happyReduce_397 = happyMonadReduce 3# 153# happyReduction_397
7440happyReduction_397 (happy_x_3 `HappyStk`
7441	happy_x_2 `HappyStk`
7442	happy_x_1 `HappyStk`
7443	happyRest) tk
7444	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7445	case happyOut173 happy_x_2 of { (HappyWrap173 happy_var_2) ->
7446	case happyOutTok happy_x_3 of { happy_var_3 ->
7447	( ams (sLL happy_var_1 happy_var_3 $ HsTupleTy noExtField HsUnboxedTuple happy_var_2)
7448                                             [mo happy_var_1,mc happy_var_3])}}})
7449	) (\r -> happyReturn (happyIn169 r))
7450
7451happyReduce_398 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7452happyReduce_398 = happyMonadReduce 3# 153# happyReduction_398
7453happyReduction_398 (happy_x_3 `HappyStk`
7454	happy_x_2 `HappyStk`
7455	happy_x_1 `HappyStk`
7456	happyRest) tk
7457	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7458	case happyOut174 happy_x_2 of { (HappyWrap174 happy_var_2) ->
7459	case happyOutTok happy_x_3 of { happy_var_3 ->
7460	( ams (sLL happy_var_1 happy_var_3 $ HsSumTy noExtField happy_var_2)
7461                                             [mo happy_var_1,mc happy_var_3])}}})
7462	) (\r -> happyReturn (happyIn169 r))
7463
7464happyReduce_399 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7465happyReduce_399 = happyMonadReduce 3# 153# happyReduction_399
7466happyReduction_399 (happy_x_3 `HappyStk`
7467	happy_x_2 `HappyStk`
7468	happy_x_1 `HappyStk`
7469	happyRest) tk
7470	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7471	case happyOut155 happy_x_2 of { (HappyWrap155 happy_var_2) ->
7472	case happyOutTok happy_x_3 of { happy_var_3 ->
7473	( ams (sLL happy_var_1 happy_var_3 $ HsListTy  noExtField happy_var_2) [mos happy_var_1,mcs happy_var_3])}}})
7474	) (\r -> happyReturn (happyIn169 r))
7475
7476happyReduce_400 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7477happyReduce_400 = happyMonadReduce 3# 153# happyReduction_400
7478happyReduction_400 (happy_x_3 `HappyStk`
7479	happy_x_2 `HappyStk`
7480	happy_x_1 `HappyStk`
7481	happyRest) tk
7482	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7483	case happyOut155 happy_x_2 of { (HappyWrap155 happy_var_2) ->
7484	case happyOutTok happy_x_3 of { happy_var_3 ->
7485	( ams (sLL happy_var_1 happy_var_3 $ HsParTy   noExtField happy_var_2) [mop happy_var_1,mcp happy_var_3])}}})
7486	) (\r -> happyReturn (happyIn169 r))
7487
7488happyReduce_401 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7489happyReduce_401 = happySpecReduce_1  153# happyReduction_401
7490happyReduction_401 happy_x_1
7491	 =  case happyOut208 happy_x_1 of { (HappyWrap208 happy_var_1) ->
7492	happyIn169
7493		 (mapLoc (HsSpliceTy noExtField) happy_var_1
7494	)}
7495
7496happyReduce_402 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7497happyReduce_402 = happySpecReduce_1  153# happyReduction_402
7498happyReduction_402 happy_x_1
7499	 =  case happyOut222 happy_x_1 of { (HappyWrap222 happy_var_1) ->
7500	happyIn169
7501		 (mapLoc (HsSpliceTy noExtField) happy_var_1
7502	)}
7503
7504happyReduce_403 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7505happyReduce_403 = happyMonadReduce 2# 153# happyReduction_403
7506happyReduction_403 (happy_x_2 `HappyStk`
7507	happy_x_1 `HappyStk`
7508	happyRest) tk
7509	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7510	case happyOut273 happy_x_2 of { (HappyWrap273 happy_var_2) ->
7511	( ams (sLL happy_var_1 happy_var_2 $ HsTyVar noExtField IsPromoted happy_var_2) [mj AnnSimpleQuote happy_var_1,mj AnnName happy_var_2])}})
7512	) (\r -> happyReturn (happyIn169 r))
7513
7514happyReduce_404 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7515happyReduce_404 = happyMonadReduce 6# 153# happyReduction_404
7516happyReduction_404 (happy_x_6 `HappyStk`
7517	happy_x_5 `HappyStk`
7518	happy_x_4 `HappyStk`
7519	happy_x_3 `HappyStk`
7520	happy_x_2 `HappyStk`
7521	happy_x_1 `HappyStk`
7522	happyRest) tk
7523	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7524	case happyOutTok happy_x_2 of { happy_var_2 ->
7525	case happyOut155 happy_x_3 of { (HappyWrap155 happy_var_3) ->
7526	case happyOutTok happy_x_4 of { happy_var_4 ->
7527	case happyOut173 happy_x_5 of { (HappyWrap173 happy_var_5) ->
7528	case happyOutTok happy_x_6 of { happy_var_6 ->
7529	( addAnnotation (gl happy_var_3) AnnComma (gl happy_var_4) >>
7530                                ams (sLL happy_var_1 happy_var_6 $ HsExplicitTupleTy noExtField (happy_var_3 : happy_var_5))
7531                                    [mj AnnSimpleQuote happy_var_1,mop happy_var_2,mcp happy_var_6])}}}}}})
7532	) (\r -> happyReturn (happyIn169 r))
7533
7534happyReduce_405 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7535happyReduce_405 = happyMonadReduce 4# 153# happyReduction_405
7536happyReduction_405 (happy_x_4 `HappyStk`
7537	happy_x_3 `HappyStk`
7538	happy_x_2 `HappyStk`
7539	happy_x_1 `HappyStk`
7540	happyRest) tk
7541	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7542	case happyOutTok happy_x_2 of { happy_var_2 ->
7543	case happyOut172 happy_x_3 of { (HappyWrap172 happy_var_3) ->
7544	case happyOutTok happy_x_4 of { happy_var_4 ->
7545	( ams (sLL happy_var_1 happy_var_4 $ HsExplicitListTy noExtField IsPromoted happy_var_3)
7546                                                       [mj AnnSimpleQuote happy_var_1,mos happy_var_2,mcs happy_var_4])}}}})
7547	) (\r -> happyReturn (happyIn169 r))
7548
7549happyReduce_406 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7550happyReduce_406 = happyMonadReduce 2# 153# happyReduction_406
7551happyReduction_406 (happy_x_2 `HappyStk`
7552	happy_x_1 `HappyStk`
7553	happyRest) tk
7554	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7555	case happyOut302 happy_x_2 of { (HappyWrap302 happy_var_2) ->
7556	( ams (sLL happy_var_1 happy_var_2 $ HsTyVar noExtField IsPromoted happy_var_2)
7557                                                       [mj AnnSimpleQuote happy_var_1,mj AnnName happy_var_2])}})
7558	) (\r -> happyReturn (happyIn169 r))
7559
7560happyReduce_407 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7561happyReduce_407 = happyMonadReduce 5# 153# happyReduction_407
7562happyReduction_407 (happy_x_5 `HappyStk`
7563	happy_x_4 `HappyStk`
7564	happy_x_3 `HappyStk`
7565	happy_x_2 `HappyStk`
7566	happy_x_1 `HappyStk`
7567	happyRest) tk
7568	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7569	case happyOut155 happy_x_2 of { (HappyWrap155 happy_var_2) ->
7570	case happyOutTok happy_x_3 of { happy_var_3 ->
7571	case happyOut173 happy_x_4 of { (HappyWrap173 happy_var_4) ->
7572	case happyOutTok happy_x_5 of { happy_var_5 ->
7573	( addAnnotation (gl happy_var_2) AnnComma
7574                                                           (gl happy_var_3) >>
7575                                             ams (sLL happy_var_1 happy_var_5 $ HsExplicitListTy noExtField NotPromoted (happy_var_2 : happy_var_4))
7576                                                 [mos happy_var_1,mcs happy_var_5])}}}}})
7577	) (\r -> happyReturn (happyIn169 r))
7578
7579happyReduce_408 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7580happyReduce_408 = happySpecReduce_1  153# happyReduction_408
7581happyReduction_408 happy_x_1
7582	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7583	happyIn169
7584		 (sLL happy_var_1 happy_var_1 $ HsTyLit noExtField $ HsNumTy (getINTEGERs happy_var_1)
7585                                                           (il_value (getINTEGER happy_var_1))
7586	)}
7587
7588happyReduce_409 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7589happyReduce_409 = happySpecReduce_1  153# happyReduction_409
7590happyReduction_409 happy_x_1
7591	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7592	happyIn169
7593		 (sLL happy_var_1 happy_var_1 $ HsTyLit noExtField $ HsStrTy (getSTRINGs happy_var_1)
7594                                                                     (getSTRING  happy_var_1)
7595	)}
7596
7597happyReduce_410 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7598happyReduce_410 = happySpecReduce_1  153# happyReduction_410
7599happyReduction_410 happy_x_1
7600	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7601	happyIn169
7602		 (sL1 happy_var_1 $ mkAnonWildCardTy
7603	)}
7604
7605happyReduce_411 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7606happyReduce_411 = happySpecReduce_1  154# happyReduction_411
7607happyReduction_411 happy_x_1
7608	 =  case happyOut149 happy_x_1 of { (HappyWrap149 happy_var_1) ->
7609	happyIn170
7610		 (mkLHsSigType happy_var_1
7611	)}
7612
7613happyReduce_412 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7614happyReduce_412 = happySpecReduce_1  155# happyReduction_412
7615happyReduction_412 happy_x_1
7616	 =  case happyOut156 happy_x_1 of { (HappyWrap156 happy_var_1) ->
7617	happyIn171
7618		 ([mkLHsSigType happy_var_1]
7619	)}
7620
7621happyReduce_413 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7622happyReduce_413 = happyMonadReduce 3# 155# happyReduction_413
7623happyReduction_413 (happy_x_3 `HappyStk`
7624	happy_x_2 `HappyStk`
7625	happy_x_1 `HappyStk`
7626	happyRest) tk
7627	 = happyThen ((case happyOut156 happy_x_1 of { (HappyWrap156 happy_var_1) ->
7628	case happyOutTok happy_x_2 of { happy_var_2 ->
7629	case happyOut171 happy_x_3 of { (HappyWrap171 happy_var_3) ->
7630	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2)
7631                                           >> return (mkLHsSigType happy_var_1 : happy_var_3))}}})
7632	) (\r -> happyReturn (happyIn171 r))
7633
7634happyReduce_414 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7635happyReduce_414 = happySpecReduce_1  156# happyReduction_414
7636happyReduction_414 happy_x_1
7637	 =  case happyOut173 happy_x_1 of { (HappyWrap173 happy_var_1) ->
7638	happyIn172
7639		 (happy_var_1
7640	)}
7641
7642happyReduce_415 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7643happyReduce_415 = happySpecReduce_0  156# happyReduction_415
7644happyReduction_415  =  happyIn172
7645		 ([]
7646	)
7647
7648happyReduce_416 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7649happyReduce_416 = happySpecReduce_1  157# happyReduction_416
7650happyReduction_416 happy_x_1
7651	 =  case happyOut155 happy_x_1 of { (HappyWrap155 happy_var_1) ->
7652	happyIn173
7653		 ([happy_var_1]
7654	)}
7655
7656happyReduce_417 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7657happyReduce_417 = happyMonadReduce 3# 157# happyReduction_417
7658happyReduction_417 (happy_x_3 `HappyStk`
7659	happy_x_2 `HappyStk`
7660	happy_x_1 `HappyStk`
7661	happyRest) tk
7662	 = happyThen ((case happyOut155 happy_x_1 of { (HappyWrap155 happy_var_1) ->
7663	case happyOutTok happy_x_2 of { happy_var_2 ->
7664	case happyOut173 happy_x_3 of { (HappyWrap173 happy_var_3) ->
7665	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2)
7666                                          >> return (happy_var_1 : happy_var_3))}}})
7667	) (\r -> happyReturn (happyIn173 r))
7668
7669happyReduce_418 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7670happyReduce_418 = happyMonadReduce 3# 158# happyReduction_418
7671happyReduction_418 (happy_x_3 `HappyStk`
7672	happy_x_2 `HappyStk`
7673	happy_x_1 `HappyStk`
7674	happyRest) tk
7675	 = happyThen ((case happyOut155 happy_x_1 of { (HappyWrap155 happy_var_1) ->
7676	case happyOutTok happy_x_2 of { happy_var_2 ->
7677	case happyOut155 happy_x_3 of { (HappyWrap155 happy_var_3) ->
7678	( addAnnotation (gl happy_var_1) AnnVbar (gl happy_var_2)
7679                                          >> return [happy_var_1,happy_var_3])}}})
7680	) (\r -> happyReturn (happyIn174 r))
7681
7682happyReduce_419 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7683happyReduce_419 = happyMonadReduce 3# 158# happyReduction_419
7684happyReduction_419 (happy_x_3 `HappyStk`
7685	happy_x_2 `HappyStk`
7686	happy_x_1 `HappyStk`
7687	happyRest) tk
7688	 = happyThen ((case happyOut155 happy_x_1 of { (HappyWrap155 happy_var_1) ->
7689	case happyOutTok happy_x_2 of { happy_var_2 ->
7690	case happyOut174 happy_x_3 of { (HappyWrap174 happy_var_3) ->
7691	( addAnnotation (gl happy_var_1) AnnVbar (gl happy_var_2)
7692                                          >> return (happy_var_1 : happy_var_3))}}})
7693	) (\r -> happyReturn (happyIn174 r))
7694
7695happyReduce_420 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7696happyReduce_420 = happySpecReduce_2  159# happyReduction_420
7697happyReduction_420 happy_x_2
7698	happy_x_1
7699	 =  case happyOut176 happy_x_1 of { (HappyWrap176 happy_var_1) ->
7700	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
7701	happyIn175
7702		 (happy_var_1 : happy_var_2
7703	)}}
7704
7705happyReduce_421 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7706happyReduce_421 = happySpecReduce_0  159# happyReduction_421
7707happyReduction_421  =  happyIn175
7708		 ([]
7709	)
7710
7711happyReduce_422 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7712happyReduce_422 = happySpecReduce_1  160# happyReduction_422
7713happyReduction_422 happy_x_1
7714	 =  case happyOut299 happy_x_1 of { (HappyWrap299 happy_var_1) ->
7715	happyIn176
7716		 (sL1 happy_var_1 (UserTyVar noExtField happy_var_1)
7717	)}
7718
7719happyReduce_423 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7720happyReduce_423 = happyMonadReduce 5# 160# happyReduction_423
7721happyReduction_423 (happy_x_5 `HappyStk`
7722	happy_x_4 `HappyStk`
7723	happy_x_3 `HappyStk`
7724	happy_x_2 `HappyStk`
7725	happy_x_1 `HappyStk`
7726	happyRest) tk
7727	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7728	case happyOut299 happy_x_2 of { (HappyWrap299 happy_var_2) ->
7729	case happyOutTok happy_x_3 of { happy_var_3 ->
7730	case happyOut181 happy_x_4 of { (HappyWrap181 happy_var_4) ->
7731	case happyOutTok happy_x_5 of { happy_var_5 ->
7732	( ams (sLL happy_var_1 happy_var_5  (KindedTyVar noExtField happy_var_2 happy_var_4))
7733                                               [mop happy_var_1,mu AnnDcolon happy_var_3
7734                                               ,mcp happy_var_5])}}}}})
7735	) (\r -> happyReturn (happyIn176 r))
7736
7737happyReduce_424 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7738happyReduce_424 = happySpecReduce_0  161# happyReduction_424
7739happyReduction_424  =  happyIn177
7740		 (noLoc ([],[])
7741	)
7742
7743happyReduce_425 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7744happyReduce_425 = happySpecReduce_2  161# happyReduction_425
7745happyReduction_425 happy_x_2
7746	happy_x_1
7747	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7748	case happyOut178 happy_x_2 of { (HappyWrap178 happy_var_2) ->
7749	happyIn177
7750		 ((sLL happy_var_1 happy_var_2 ([mj AnnVbar happy_var_1]
7751                                                 ,reverse (unLoc happy_var_2)))
7752	)}}
7753
7754happyReduce_426 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7755happyReduce_426 = happyMonadReduce 3# 162# happyReduction_426
7756happyReduction_426 (happy_x_3 `HappyStk`
7757	happy_x_2 `HappyStk`
7758	happy_x_1 `HappyStk`
7759	happyRest) tk
7760	 = happyThen ((case happyOut178 happy_x_1 of { (HappyWrap178 happy_var_1) ->
7761	case happyOutTok happy_x_2 of { happy_var_2 ->
7762	case happyOut179 happy_x_3 of { (HappyWrap179 happy_var_3) ->
7763	( addAnnotation (gl $ head $ unLoc happy_var_1) AnnComma (gl happy_var_2)
7764                           >> return (sLL happy_var_1 happy_var_3 (happy_var_3 : unLoc happy_var_1)))}}})
7765	) (\r -> happyReturn (happyIn178 r))
7766
7767happyReduce_427 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7768happyReduce_427 = happySpecReduce_1  162# happyReduction_427
7769happyReduction_427 happy_x_1
7770	 =  case happyOut179 happy_x_1 of { (HappyWrap179 happy_var_1) ->
7771	happyIn178
7772		 (sL1 happy_var_1 [happy_var_1]
7773	)}
7774
7775happyReduce_428 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7776happyReduce_428 = happyMonadReduce 3# 163# happyReduction_428
7777happyReduction_428 (happy_x_3 `HappyStk`
7778	happy_x_2 `HappyStk`
7779	happy_x_1 `HappyStk`
7780	happyRest) tk
7781	 = happyThen ((case happyOut180 happy_x_1 of { (HappyWrap180 happy_var_1) ->
7782	case happyOutTok happy_x_2 of { happy_var_2 ->
7783	case happyOut180 happy_x_3 of { (HappyWrap180 happy_var_3) ->
7784	( ams (cL (comb3 happy_var_1 happy_var_2 happy_var_3)
7785                                       (reverse (unLoc happy_var_1), reverse (unLoc happy_var_3)))
7786                                       [mu AnnRarrow happy_var_2])}}})
7787	) (\r -> happyReturn (happyIn179 r))
7788
7789happyReduce_429 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7790happyReduce_429 = happySpecReduce_0  164# happyReduction_429
7791happyReduction_429  =  happyIn180
7792		 (noLoc []
7793	)
7794
7795happyReduce_430 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7796happyReduce_430 = happySpecReduce_2  164# happyReduction_430
7797happyReduction_430 happy_x_2
7798	happy_x_1
7799	 =  case happyOut180 happy_x_1 of { (HappyWrap180 happy_var_1) ->
7800	case happyOut299 happy_x_2 of { (HappyWrap299 happy_var_2) ->
7801	happyIn180
7802		 (sLL happy_var_1 happy_var_2 (happy_var_2 : unLoc happy_var_1)
7803	)}}
7804
7805happyReduce_431 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7806happyReduce_431 = happySpecReduce_1  165# happyReduction_431
7807happyReduction_431 happy_x_1
7808	 =  case happyOut157 happy_x_1 of { (HappyWrap157 happy_var_1) ->
7809	happyIn181
7810		 (happy_var_1
7811	)}
7812
7813happyReduce_432 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7814happyReduce_432 = happyMonadReduce 4# 166# happyReduction_432
7815happyReduction_432 (happy_x_4 `HappyStk`
7816	happy_x_3 `HappyStk`
7817	happy_x_2 `HappyStk`
7818	happy_x_1 `HappyStk`
7819	happyRest) tk
7820	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7821	case happyOutTok happy_x_2 of { happy_var_2 ->
7822	case happyOut183 happy_x_3 of { (HappyWrap183 happy_var_3) ->
7823	case happyOutTok happy_x_4 of { happy_var_4 ->
7824	( checkEmptyGADTs $
7825                                                      cL (comb2 happy_var_1 happy_var_3)
7826                                                        ([mj AnnWhere happy_var_1
7827                                                         ,moc happy_var_2
7828                                                         ,mcc happy_var_4]
7829                                                        , unLoc happy_var_3))}}}})
7830	) (\r -> happyReturn (happyIn182 r))
7831
7832happyReduce_433 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7833happyReduce_433 = happyMonadReduce 4# 166# happyReduction_433
7834happyReduction_433 (happy_x_4 `HappyStk`
7835	happy_x_3 `HappyStk`
7836	happy_x_2 `HappyStk`
7837	happy_x_1 `HappyStk`
7838	happyRest) tk
7839	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
7840	case happyOut183 happy_x_3 of { (HappyWrap183 happy_var_3) ->
7841	( checkEmptyGADTs $
7842                                                      cL (comb2 happy_var_1 happy_var_3)
7843                                                        ([mj AnnWhere happy_var_1]
7844                                                        , unLoc happy_var_3))}})
7845	) (\r -> happyReturn (happyIn182 r))
7846
7847happyReduce_434 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7848happyReduce_434 = happySpecReduce_0  166# happyReduction_434
7849happyReduction_434  =  happyIn182
7850		 (noLoc ([],[])
7851	)
7852
7853happyReduce_435 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7854happyReduce_435 = happyMonadReduce 3# 167# happyReduction_435
7855happyReduction_435 (happy_x_3 `HappyStk`
7856	happy_x_2 `HappyStk`
7857	happy_x_1 `HappyStk`
7858	happyRest) tk
7859	 = happyThen ((case happyOut184 happy_x_1 of { (HappyWrap184 happy_var_1) ->
7860	case happyOutTok happy_x_2 of { happy_var_2 ->
7861	case happyOut183 happy_x_3 of { (HappyWrap183 happy_var_3) ->
7862	( addAnnotation (gl happy_var_1) AnnSemi (gl happy_var_2)
7863                     >> return (cL (comb2 happy_var_1 happy_var_3) (happy_var_1 : unLoc happy_var_3)))}}})
7864	) (\r -> happyReturn (happyIn183 r))
7865
7866happyReduce_436 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7867happyReduce_436 = happySpecReduce_1  167# happyReduction_436
7868happyReduction_436 happy_x_1
7869	 =  case happyOut184 happy_x_1 of { (HappyWrap184 happy_var_1) ->
7870	happyIn183
7871		 (cL (gl happy_var_1) [happy_var_1]
7872	)}
7873
7874happyReduce_437 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7875happyReduce_437 = happySpecReduce_0  167# happyReduction_437
7876happyReduction_437  =  happyIn183
7877		 (noLoc []
7878	)
7879
7880happyReduce_438 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7881happyReduce_438 = happyMonadReduce 3# 168# happyReduction_438
7882happyReduction_438 (happy_x_3 `HappyStk`
7883	happy_x_2 `HappyStk`
7884	happy_x_1 `HappyStk`
7885	happyRest) tk
7886	 = happyThen ((case happyOut329 happy_x_1 of { (HappyWrap329 happy_var_1) ->
7887	case happyOut185 happy_x_3 of { (HappyWrap185 happy_var_3) ->
7888	( return $ addConDoc happy_var_3 happy_var_1)}})
7889	) (\r -> happyReturn (happyIn184 r))
7890
7891happyReduce_439 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7892happyReduce_439 = happyMonadReduce 1# 168# happyReduction_439
7893happyReduction_439 (happy_x_1 `HappyStk`
7894	happyRest) tk
7895	 = happyThen ((case happyOut185 happy_x_1 of { (HappyWrap185 happy_var_1) ->
7896	( return happy_var_1)})
7897	) (\r -> happyReturn (happyIn184 r))
7898
7899happyReduce_440 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7900happyReduce_440 = happyMonadReduce 3# 169# happyReduction_440
7901happyReduction_440 (happy_x_3 `HappyStk`
7902	happy_x_2 `HappyStk`
7903	happy_x_1 `HappyStk`
7904	happyRest) tk
7905	 = happyThen ((case happyOut277 happy_x_1 of { (HappyWrap277 happy_var_1) ->
7906	case happyOutTok happy_x_2 of { happy_var_2 ->
7907	case happyOut150 happy_x_3 of { (HappyWrap150 happy_var_3) ->
7908	( let (gadt,anns) = mkGadtDecl (unLoc happy_var_1) happy_var_3
7909                   in ams (sLL happy_var_1 happy_var_3 gadt)
7910                       (mu AnnDcolon happy_var_2:anns))}}})
7911	) (\r -> happyReturn (happyIn185 r))
7912
7913happyReduce_441 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7914happyReduce_441 = happySpecReduce_3  170# happyReduction_441
7915happyReduction_441 happy_x_3
7916	happy_x_2
7917	happy_x_1
7918	 =  case happyOut329 happy_x_1 of { (HappyWrap329 happy_var_1) ->
7919	case happyOutTok happy_x_2 of { happy_var_2 ->
7920	case happyOut187 happy_x_3 of { (HappyWrap187 happy_var_3) ->
7921	happyIn186
7922		 (cL (comb2 happy_var_2 happy_var_3) ([mj AnnEqual happy_var_2]
7923                                                     ,addConDocs (unLoc happy_var_3) happy_var_1)
7924	)}}}
7925
7926happyReduce_442 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7927happyReduce_442 = happyMonadReduce 5# 171# happyReduction_442
7928happyReduction_442 (happy_x_5 `HappyStk`
7929	happy_x_4 `HappyStk`
7930	happy_x_3 `HappyStk`
7931	happy_x_2 `HappyStk`
7932	happy_x_1 `HappyStk`
7933	happyRest) tk
7934	 = happyThen ((case happyOut187 happy_x_1 of { (HappyWrap187 happy_var_1) ->
7935	case happyOut329 happy_x_2 of { (HappyWrap329 happy_var_2) ->
7936	case happyOutTok happy_x_3 of { happy_var_3 ->
7937	case happyOut328 happy_x_4 of { (HappyWrap328 happy_var_4) ->
7938	case happyOut188 happy_x_5 of { (HappyWrap188 happy_var_5) ->
7939	( addAnnotation (gl $ head $ unLoc happy_var_1) AnnVbar (gl happy_var_3)
7940               >> return (sLL happy_var_1 happy_var_5 (addConDoc happy_var_5 happy_var_2 : addConDocFirst (unLoc happy_var_1) happy_var_4)))}}}}})
7941	) (\r -> happyReturn (happyIn187 r))
7942
7943happyReduce_443 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7944happyReduce_443 = happySpecReduce_1  171# happyReduction_443
7945happyReduction_443 happy_x_1
7946	 =  case happyOut188 happy_x_1 of { (HappyWrap188 happy_var_1) ->
7947	happyIn187
7948		 (sL1 happy_var_1 [happy_var_1]
7949	)}
7950
7951happyReduce_444 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7952happyReduce_444 = happyMonadReduce 5# 172# happyReduction_444
7953happyReduction_444 (happy_x_5 `HappyStk`
7954	happy_x_4 `HappyStk`
7955	happy_x_3 `HappyStk`
7956	happy_x_2 `HappyStk`
7957	happy_x_1 `HappyStk`
7958	happyRest) tk
7959	 = happyThen ((case happyOut329 happy_x_1 of { (HappyWrap329 happy_var_1) ->
7960	case happyOut189 happy_x_2 of { (HappyWrap189 happy_var_2) ->
7961	case happyOut160 happy_x_3 of { (HappyWrap160 happy_var_3) ->
7962	case happyOutTok happy_x_4 of { happy_var_4 ->
7963	case happyOut190 happy_x_5 of { (HappyWrap190 happy_var_5) ->
7964	( ams (let (con,details,doc_prev) = unLoc happy_var_5 in
7965                  addConDoc (cL (comb4 happy_var_2 happy_var_3 happy_var_4 happy_var_5) (mkConDeclH98 con
7966                                                       (snd $ unLoc happy_var_2)
7967                                                       (Just happy_var_3)
7968                                                       details))
7969                            (happy_var_1 `mplus` doc_prev))
7970                        (mu AnnDarrow happy_var_4:(fst $ unLoc happy_var_2)))}}}}})
7971	) (\r -> happyReturn (happyIn188 r))
7972
7973happyReduce_445 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7974happyReduce_445 = happyMonadReduce 3# 172# happyReduction_445
7975happyReduction_445 (happy_x_3 `HappyStk`
7976	happy_x_2 `HappyStk`
7977	happy_x_1 `HappyStk`
7978	happyRest) tk
7979	 = happyThen ((case happyOut329 happy_x_1 of { (HappyWrap329 happy_var_1) ->
7980	case happyOut189 happy_x_2 of { (HappyWrap189 happy_var_2) ->
7981	case happyOut190 happy_x_3 of { (HappyWrap190 happy_var_3) ->
7982	( ams ( let (con,details,doc_prev) = unLoc happy_var_3 in
7983                  addConDoc (cL (comb2 happy_var_2 happy_var_3) (mkConDeclH98 con
7984                                                      (snd $ unLoc happy_var_2)
7985                                                      Nothing   -- No context
7986                                                      details))
7987                            (happy_var_1 `mplus` doc_prev))
7988                       (fst $ unLoc happy_var_2))}}})
7989	) (\r -> happyReturn (happyIn188 r))
7990
7991happyReduce_446 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
7992happyReduce_446 = happySpecReduce_3  173# happyReduction_446
7993happyReduction_446 happy_x_3
7994	happy_x_2
7995	happy_x_1
7996	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
7997	case happyOut175 happy_x_2 of { (HappyWrap175 happy_var_2) ->
7998	case happyOutTok happy_x_3 of { happy_var_3 ->
7999	happyIn189
8000		 (sLL happy_var_1 happy_var_3 ([mu AnnForall happy_var_1,mj AnnDot happy_var_3], Just happy_var_2)
8001	)}}}
8002
8003happyReduce_447 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8004happyReduce_447 = happySpecReduce_0  173# happyReduction_447
8005happyReduction_447  =  happyIn189
8006		 (noLoc ([], Nothing)
8007	)
8008
8009happyReduce_448 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8010happyReduce_448 = happyMonadReduce 1# 174# happyReduction_448
8011happyReduction_448 (happy_x_1 `HappyStk`
8012	happyRest) tk
8013	 = happyThen ((case happyOut164 happy_x_1 of { (HappyWrap164 happy_var_1) ->
8014	( do { c <- mergeDataCon (unLoc happy_var_1)
8015                                                 ; return $ sL1 happy_var_1 c })})
8016	) (\r -> happyReturn (happyIn190 r))
8017
8018happyReduce_449 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8019happyReduce_449 = happySpecReduce_0  175# happyReduction_449
8020happyReduction_449  =  happyIn191
8021		 ([]
8022	)
8023
8024happyReduce_450 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8025happyReduce_450 = happySpecReduce_1  175# happyReduction_450
8026happyReduction_450 happy_x_1
8027	 =  case happyOut192 happy_x_1 of { (HappyWrap192 happy_var_1) ->
8028	happyIn191
8029		 (happy_var_1
8030	)}
8031
8032happyReduce_451 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8033happyReduce_451 = happyMonadReduce 5# 176# happyReduction_451
8034happyReduction_451 (happy_x_5 `HappyStk`
8035	happy_x_4 `HappyStk`
8036	happy_x_3 `HappyStk`
8037	happy_x_2 `HappyStk`
8038	happy_x_1 `HappyStk`
8039	happyRest) tk
8040	 = happyThen ((case happyOut193 happy_x_1 of { (HappyWrap193 happy_var_1) ->
8041	case happyOut329 happy_x_2 of { (HappyWrap329 happy_var_2) ->
8042	case happyOutTok happy_x_3 of { happy_var_3 ->
8043	case happyOut328 happy_x_4 of { (HappyWrap328 happy_var_4) ->
8044	case happyOut192 happy_x_5 of { (HappyWrap192 happy_var_5) ->
8045	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_3) >>
8046               return ((addFieldDoc happy_var_1 happy_var_4) : addFieldDocs happy_var_5 happy_var_2))}}}}})
8047	) (\r -> happyReturn (happyIn192 r))
8048
8049happyReduce_452 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8050happyReduce_452 = happySpecReduce_1  176# happyReduction_452
8051happyReduction_452 happy_x_1
8052	 =  case happyOut193 happy_x_1 of { (HappyWrap193 happy_var_1) ->
8053	happyIn192
8054		 ([happy_var_1]
8055	)}
8056
8057happyReduce_453 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8058happyReduce_453 = happyMonadReduce 5# 177# happyReduction_453
8059happyReduction_453 (happy_x_5 `HappyStk`
8060	happy_x_4 `HappyStk`
8061	happy_x_3 `HappyStk`
8062	happy_x_2 `HappyStk`
8063	happy_x_1 `HappyStk`
8064	happyRest) tk
8065	 = happyThen ((case happyOut329 happy_x_1 of { (HappyWrap329 happy_var_1) ->
8066	case happyOut151 happy_x_2 of { (HappyWrap151 happy_var_2) ->
8067	case happyOutTok happy_x_3 of { happy_var_3 ->
8068	case happyOut157 happy_x_4 of { (HappyWrap157 happy_var_4) ->
8069	case happyOut328 happy_x_5 of { (HappyWrap328 happy_var_5) ->
8070	( ams (cL (comb2 happy_var_2 happy_var_4)
8071                      (ConDeclField noExtField (reverse (map (\ln@(dL->L l n) -> cL l $ FieldOcc noExtField ln) (unLoc happy_var_2))) happy_var_4 (happy_var_1 `mplus` happy_var_5)))
8072                   [mu AnnDcolon happy_var_3])}}}}})
8073	) (\r -> happyReturn (happyIn193 r))
8074
8075happyReduce_454 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8076happyReduce_454 = happySpecReduce_0  178# happyReduction_454
8077happyReduction_454  =  happyIn194
8078		 (noLoc []
8079	)
8080
8081happyReduce_455 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8082happyReduce_455 = happySpecReduce_1  178# happyReduction_455
8083happyReduction_455 happy_x_1
8084	 =  case happyOut195 happy_x_1 of { (HappyWrap195 happy_var_1) ->
8085	happyIn194
8086		 (happy_var_1
8087	)}
8088
8089happyReduce_456 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8090happyReduce_456 = happySpecReduce_2  179# happyReduction_456
8091happyReduction_456 happy_x_2
8092	happy_x_1
8093	 =  case happyOut195 happy_x_1 of { (HappyWrap195 happy_var_1) ->
8094	case happyOut196 happy_x_2 of { (HappyWrap196 happy_var_2) ->
8095	happyIn195
8096		 (sLL happy_var_1 happy_var_2 $ happy_var_2 : unLoc happy_var_1
8097	)}}
8098
8099happyReduce_457 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8100happyReduce_457 = happySpecReduce_1  179# happyReduction_457
8101happyReduction_457 happy_x_1
8102	 =  case happyOut196 happy_x_1 of { (HappyWrap196 happy_var_1) ->
8103	happyIn195
8104		 (sLL happy_var_1 happy_var_1 [happy_var_1]
8105	)}
8106
8107happyReduce_458 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8108happyReduce_458 = happyMonadReduce 2# 180# happyReduction_458
8109happyReduction_458 (happy_x_2 `HappyStk`
8110	happy_x_1 `HappyStk`
8111	happyRest) tk
8112	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8113	case happyOut197 happy_x_2 of { (HappyWrap197 happy_var_2) ->
8114	( let { full_loc = comb2 happy_var_1 happy_var_2 }
8115                 in ams (cL full_loc $ HsDerivingClause noExtField Nothing happy_var_2)
8116                        [mj AnnDeriving happy_var_1])}})
8117	) (\r -> happyReturn (happyIn196 r))
8118
8119happyReduce_459 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8120happyReduce_459 = happyMonadReduce 3# 180# happyReduction_459
8121happyReduction_459 (happy_x_3 `HappyStk`
8122	happy_x_2 `HappyStk`
8123	happy_x_1 `HappyStk`
8124	happyRest) tk
8125	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8126	case happyOut84 happy_x_2 of { (HappyWrap84 happy_var_2) ->
8127	case happyOut197 happy_x_3 of { (HappyWrap197 happy_var_3) ->
8128	( let { full_loc = comb2 happy_var_1 happy_var_3 }
8129                 in ams (cL full_loc $ HsDerivingClause noExtField (Just happy_var_2) happy_var_3)
8130                        [mj AnnDeriving happy_var_1])}}})
8131	) (\r -> happyReturn (happyIn196 r))
8132
8133happyReduce_460 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8134happyReduce_460 = happyMonadReduce 3# 180# happyReduction_460
8135happyReduction_460 (happy_x_3 `HappyStk`
8136	happy_x_2 `HappyStk`
8137	happy_x_1 `HappyStk`
8138	happyRest) tk
8139	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8140	case happyOut197 happy_x_2 of { (HappyWrap197 happy_var_2) ->
8141	case happyOut85 happy_x_3 of { (HappyWrap85 happy_var_3) ->
8142	( let { full_loc = comb2 happy_var_1 happy_var_3 }
8143                 in ams (cL full_loc $ HsDerivingClause noExtField (Just happy_var_3) happy_var_2)
8144                        [mj AnnDeriving happy_var_1])}}})
8145	) (\r -> happyReturn (happyIn196 r))
8146
8147happyReduce_461 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8148happyReduce_461 = happySpecReduce_1  181# happyReduction_461
8149happyReduction_461 happy_x_1
8150	 =  case happyOut288 happy_x_1 of { (HappyWrap288 happy_var_1) ->
8151	happyIn197
8152		 (sL1 happy_var_1 [mkLHsSigType happy_var_1]
8153	)}
8154
8155happyReduce_462 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8156happyReduce_462 = happyMonadReduce 2# 181# happyReduction_462
8157happyReduction_462 (happy_x_2 `HappyStk`
8158	happy_x_1 `HappyStk`
8159	happyRest) tk
8160	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8161	case happyOutTok happy_x_2 of { happy_var_2 ->
8162	( ams (sLL happy_var_1 happy_var_2 [])
8163                                     [mop happy_var_1,mcp happy_var_2])}})
8164	) (\r -> happyReturn (happyIn197 r))
8165
8166happyReduce_463 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8167happyReduce_463 = happyMonadReduce 3# 181# happyReduction_463
8168happyReduction_463 (happy_x_3 `HappyStk`
8169	happy_x_2 `HappyStk`
8170	happy_x_1 `HappyStk`
8171	happyRest) tk
8172	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8173	case happyOut171 happy_x_2 of { (HappyWrap171 happy_var_2) ->
8174	case happyOutTok happy_x_3 of { happy_var_3 ->
8175	( ams (sLL happy_var_1 happy_var_3 happy_var_2)
8176                                     [mop happy_var_1,mcp happy_var_3])}}})
8177	) (\r -> happyReturn (happyIn197 r))
8178
8179happyReduce_464 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8180happyReduce_464 = happySpecReduce_1  182# happyReduction_464
8181happyReduction_464 happy_x_1
8182	 =  case happyOut199 happy_x_1 of { (HappyWrap199 happy_var_1) ->
8183	happyIn198
8184		 (sL1 happy_var_1 (DocD noExtField (unLoc happy_var_1))
8185	)}
8186
8187happyReduce_465 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8188happyReduce_465 = happySpecReduce_1  183# happyReduction_465
8189happyReduction_465 happy_x_1
8190	 =  case happyOut323 happy_x_1 of { (HappyWrap323 happy_var_1) ->
8191	happyIn199
8192		 (sL1 happy_var_1 (DocCommentNext (unLoc happy_var_1))
8193	)}
8194
8195happyReduce_466 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8196happyReduce_466 = happySpecReduce_1  183# happyReduction_466
8197happyReduction_466 happy_x_1
8198	 =  case happyOut324 happy_x_1 of { (HappyWrap324 happy_var_1) ->
8199	happyIn199
8200		 (sL1 happy_var_1 (DocCommentPrev (unLoc happy_var_1))
8201	)}
8202
8203happyReduce_467 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8204happyReduce_467 = happySpecReduce_1  183# happyReduction_467
8205happyReduction_467 happy_x_1
8206	 =  case happyOut325 happy_x_1 of { (HappyWrap325 happy_var_1) ->
8207	happyIn199
8208		 (sL1 happy_var_1 (case (unLoc happy_var_1) of (n, doc) -> DocCommentNamed n doc)
8209	)}
8210
8211happyReduce_468 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8212happyReduce_468 = happySpecReduce_1  183# happyReduction_468
8213happyReduction_468 happy_x_1
8214	 =  case happyOut326 happy_x_1 of { (HappyWrap326 happy_var_1) ->
8215	happyIn199
8216		 (sL1 happy_var_1 (case (unLoc happy_var_1) of (n, doc) -> DocGroup n doc)
8217	)}
8218
8219happyReduce_469 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8220happyReduce_469 = happySpecReduce_1  184# happyReduction_469
8221happyReduction_469 happy_x_1
8222	 =  case happyOut205 happy_x_1 of { (HappyWrap205 happy_var_1) ->
8223	happyIn200
8224		 (happy_var_1
8225	)}
8226
8227happyReduce_470 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8228happyReduce_470 = happyMonadReduce 3# 184# happyReduction_470
8229happyReduction_470 (happy_x_3 `HappyStk`
8230	happy_x_2 `HappyStk`
8231	happy_x_1 `HappyStk`
8232	happyRest) tk
8233	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8234	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
8235	case happyOut202 happy_x_3 of { (HappyWrap202 happy_var_3) ->
8236	( runECP_P happy_var_2 >>= \ happy_var_2 ->
8237                                   do { let { e = patBuilderBang (getLoc happy_var_1) happy_var_2
8238                                            ; l = comb2 happy_var_1 happy_var_3 };
8239                                        (ann, r) <- checkValDef SrcStrict e Nothing happy_var_3 ;
8240                                        runPV $ hintBangPat (comb2 happy_var_1 happy_var_2) (unLoc e) ;
8241                                        -- Depending upon what the pattern looks like we might get either
8242                                        -- a FunBind or PatBind back from checkValDef. See Note
8243                                        -- [FunBind vs PatBind]
8244                                        case r of {
8245                                          (FunBind _ n _ _ _) ->
8246                                                amsL l [mj AnnFunId n] >> return () ;
8247                                          (PatBind _ (dL->L l _) _rhs _) ->
8248                                                amsL l [] >> return () } ;
8249
8250                                        _ <- amsL l (ann ++ fst (unLoc happy_var_3) ++ [mj AnnBang happy_var_1]) ;
8251                                        return $! (sL l $ ValD noExtField r) })}}})
8252	) (\r -> happyReturn (happyIn200 r))
8253
8254happyReduce_471 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8255happyReduce_471 = happyMonadReduce 3# 184# happyReduction_471
8256happyReduction_471 (happy_x_3 `HappyStk`
8257	happy_x_2 `HappyStk`
8258	happy_x_1 `HappyStk`
8259	happyRest) tk
8260	 = happyThen ((case happyOut211 happy_x_1 of { (HappyWrap211 happy_var_1) ->
8261	case happyOut147 happy_x_2 of { (HappyWrap147 happy_var_2) ->
8262	case happyOut202 happy_x_3 of { (HappyWrap202 happy_var_3) ->
8263	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8264                                       do { (ann,r) <- checkValDef NoSrcStrict happy_var_1 (snd happy_var_2) happy_var_3;
8265                                        let { l = comb2 happy_var_1 happy_var_3 };
8266                                        -- Depending upon what the pattern looks like we might get either
8267                                        -- a FunBind or PatBind back from checkValDef. See Note
8268                                        -- [FunBind vs PatBind]
8269                                        case r of {
8270                                          (FunBind _ n _ _ _) ->
8271                                                amsL l (mj AnnFunId n:(fst happy_var_2)) >> return () ;
8272                                          (PatBind _ (dL->L lh _lhs) _rhs _) ->
8273                                                amsL lh (fst happy_var_2) >> return () } ;
8274                                        _ <- amsL l (ann ++ (fst $ unLoc happy_var_3));
8275                                        return $! (sL l $ ValD noExtField r) })}}})
8276	) (\r -> happyReturn (happyIn200 r))
8277
8278happyReduce_472 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8279happyReduce_472 = happySpecReduce_1  184# happyReduction_472
8280happyReduction_472 happy_x_1
8281	 =  case happyOut111 happy_x_1 of { (HappyWrap111 happy_var_1) ->
8282	happyIn200
8283		 (happy_var_1
8284	)}
8285
8286happyReduce_473 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8287happyReduce_473 = happySpecReduce_1  184# happyReduction_473
8288happyReduction_473 happy_x_1
8289	 =  case happyOut198 happy_x_1 of { (HappyWrap198 happy_var_1) ->
8290	happyIn200
8291		 (happy_var_1
8292	)}
8293
8294happyReduce_474 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8295happyReduce_474 = happySpecReduce_1  185# happyReduction_474
8296happyReduction_474 happy_x_1
8297	 =  case happyOut200 happy_x_1 of { (HappyWrap200 happy_var_1) ->
8298	happyIn201
8299		 (happy_var_1
8300	)}
8301
8302happyReduce_475 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8303happyReduce_475 = happySpecReduce_1  185# happyReduction_475
8304happyReduction_475 happy_x_1
8305	 =  case happyOut221 happy_x_1 of { (HappyWrap221 happy_var_1) ->
8306	happyIn201
8307		 (sLL happy_var_1 happy_var_1 $ mkSpliceDecl happy_var_1
8308	)}
8309
8310happyReduce_476 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8311happyReduce_476 = happyMonadReduce 3# 186# happyReduction_476
8312happyReduction_476 (happy_x_3 `HappyStk`
8313	happy_x_2 `HappyStk`
8314	happy_x_1 `HappyStk`
8315	happyRest) tk
8316	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8317	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
8318	case happyOut128 happy_x_3 of { (HappyWrap128 happy_var_3) ->
8319	( runECP_P happy_var_2 >>= \ happy_var_2 -> return $
8320                                  sL (comb3 happy_var_1 happy_var_2 happy_var_3)
8321                                    ((mj AnnEqual happy_var_1 : (fst $ unLoc happy_var_3))
8322                                    ,GRHSs noExtField (unguardedRHS (comb3 happy_var_1 happy_var_2 happy_var_3) happy_var_2)
8323                                   (snd $ unLoc happy_var_3)))}}})
8324	) (\r -> happyReturn (happyIn202 r))
8325
8326happyReduce_477 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8327happyReduce_477 = happySpecReduce_2  186# happyReduction_477
8328happyReduction_477 happy_x_2
8329	happy_x_1
8330	 =  case happyOut203 happy_x_1 of { (HappyWrap203 happy_var_1) ->
8331	case happyOut128 happy_x_2 of { (HappyWrap128 happy_var_2) ->
8332	happyIn202
8333		 (sLL happy_var_1 happy_var_2  (fst $ unLoc happy_var_2
8334                                    ,GRHSs noExtField (reverse (unLoc happy_var_1))
8335                                                    (snd $ unLoc happy_var_2))
8336	)}}
8337
8338happyReduce_478 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8339happyReduce_478 = happySpecReduce_2  187# happyReduction_478
8340happyReduction_478 happy_x_2
8341	happy_x_1
8342	 =  case happyOut203 happy_x_1 of { (HappyWrap203 happy_var_1) ->
8343	case happyOut204 happy_x_2 of { (HappyWrap204 happy_var_2) ->
8344	happyIn203
8345		 (sLL happy_var_1 happy_var_2 (happy_var_2 : unLoc happy_var_1)
8346	)}}
8347
8348happyReduce_479 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8349happyReduce_479 = happySpecReduce_1  187# happyReduction_479
8350happyReduction_479 happy_x_1
8351	 =  case happyOut204 happy_x_1 of { (HappyWrap204 happy_var_1) ->
8352	happyIn203
8353		 (sL1 happy_var_1 [happy_var_1]
8354	)}
8355
8356happyReduce_480 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8357happyReduce_480 = happyMonadReduce 4# 188# happyReduction_480
8358happyReduction_480 (happy_x_4 `HappyStk`
8359	happy_x_3 `HappyStk`
8360	happy_x_2 `HappyStk`
8361	happy_x_1 `HappyStk`
8362	happyRest) tk
8363	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8364	case happyOut238 happy_x_2 of { (HappyWrap238 happy_var_2) ->
8365	case happyOutTok happy_x_3 of { happy_var_3 ->
8366	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
8367	( runECP_P happy_var_4 >>= \ happy_var_4 ->
8368                                     ams (sL (comb2 happy_var_1 happy_var_4) $ GRHS noExtField (unLoc happy_var_2) happy_var_4)
8369                                         [mj AnnVbar happy_var_1,mj AnnEqual happy_var_3])}}}})
8370	) (\r -> happyReturn (happyIn204 r))
8371
8372happyReduce_481 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8373happyReduce_481 = happyMonadReduce 3# 189# happyReduction_481
8374happyReduction_481 (happy_x_3 `HappyStk`
8375	happy_x_2 `HappyStk`
8376	happy_x_1 `HappyStk`
8377	happyRest) tk
8378	 = happyThen ((case happyOut211 happy_x_1 of { (HappyWrap211 happy_var_1) ->
8379	case happyOutTok happy_x_2 of { happy_var_2 ->
8380	case happyOut150 happy_x_3 of { (HappyWrap150 happy_var_3) ->
8381	( do { happy_var_1 <- runECP_P happy_var_1
8382                              ; v <- checkValSigLhs happy_var_1
8383                              ; _ <- amsL (comb2 happy_var_1 happy_var_3) [mu AnnDcolon happy_var_2]
8384                              ; return (sLL happy_var_1 happy_var_3 $ SigD noExtField $
8385                                  TypeSig noExtField [v] (mkLHsSigWcType happy_var_3))})}}})
8386	) (\r -> happyReturn (happyIn205 r))
8387
8388happyReduce_482 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8389happyReduce_482 = happyMonadReduce 5# 189# happyReduction_482
8390happyReduction_482 (happy_x_5 `HappyStk`
8391	happy_x_4 `HappyStk`
8392	happy_x_3 `HappyStk`
8393	happy_x_2 `HappyStk`
8394	happy_x_1 `HappyStk`
8395	happyRest) tk
8396	 = happyThen ((case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
8397	case happyOutTok happy_x_2 of { happy_var_2 ->
8398	case happyOut151 happy_x_3 of { (HappyWrap151 happy_var_3) ->
8399	case happyOutTok happy_x_4 of { happy_var_4 ->
8400	case happyOut150 happy_x_5 of { (HappyWrap150 happy_var_5) ->
8401	( do { let sig = TypeSig noExtField (happy_var_1 : reverse (unLoc happy_var_3))
8402                                     (mkLHsSigWcType happy_var_5)
8403                 ; addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2)
8404                 ; ams ( sLL happy_var_1 happy_var_5 $ SigD noExtField sig )
8405                       [mu AnnDcolon happy_var_4] })}}}}})
8406	) (\r -> happyReturn (happyIn205 r))
8407
8408happyReduce_483 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8409happyReduce_483 = happyMonadReduce 3# 189# happyReduction_483
8410happyReduction_483 (happy_x_3 `HappyStk`
8411	happy_x_2 `HappyStk`
8412	happy_x_1 `HappyStk`
8413	happyRest) tk
8414	 = happyThen ((case happyOut73 happy_x_1 of { (HappyWrap73 happy_var_1) ->
8415	case happyOut72 happy_x_2 of { (HappyWrap72 happy_var_2) ->
8416	case happyOut74 happy_x_3 of { (HappyWrap74 happy_var_3) ->
8417	( checkPrecP happy_var_2 happy_var_3 >>
8418                 ams (sLL happy_var_1 happy_var_3 $ SigD noExtField
8419                        (FixSig noExtField (FixitySig noExtField (fromOL $ unLoc happy_var_3)
8420                                (Fixity (fst $ unLoc happy_var_2) (snd $ unLoc happy_var_2) (unLoc happy_var_1)))))
8421                     [mj AnnInfix happy_var_1,mj AnnVal happy_var_2])}}})
8422	) (\r -> happyReturn (happyIn205 r))
8423
8424happyReduce_484 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8425happyReduce_484 = happySpecReduce_1  189# happyReduction_484
8426happyReduction_484 happy_x_1
8427	 =  case happyOut116 happy_x_1 of { (HappyWrap116 happy_var_1) ->
8428	happyIn205
8429		 (sLL happy_var_1 happy_var_1 . SigD noExtField . unLoc $ happy_var_1
8430	)}
8431
8432happyReduce_485 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8433happyReduce_485 = happyMonadReduce 4# 189# happyReduction_485
8434happyReduction_485 (happy_x_4 `HappyStk`
8435	happy_x_3 `HappyStk`
8436	happy_x_2 `HappyStk`
8437	happy_x_1 `HappyStk`
8438	happyRest) tk
8439	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8440	case happyOut277 happy_x_2 of { (HappyWrap277 happy_var_2) ->
8441	case happyOut148 happy_x_3 of { (HappyWrap148 happy_var_3) ->
8442	case happyOutTok happy_x_4 of { happy_var_4 ->
8443	( let (dcolon, tc) = happy_var_3
8444                   in ams
8445                       (sLL happy_var_1 happy_var_4
8446                         (SigD noExtField (CompleteMatchSig noExtField (getCOMPLETE_PRAGs happy_var_1) happy_var_2 tc)))
8447                    ([ mo happy_var_1 ] ++ dcolon ++ [mc happy_var_4]))}}}})
8448	) (\r -> happyReturn (happyIn205 r))
8449
8450happyReduce_486 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8451happyReduce_486 = happyMonadReduce 4# 189# happyReduction_486
8452happyReduction_486 (happy_x_4 `HappyStk`
8453	happy_x_3 `HappyStk`
8454	happy_x_2 `HappyStk`
8455	happy_x_1 `HappyStk`
8456	happyRest) tk
8457	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8458	case happyOut206 happy_x_2 of { (HappyWrap206 happy_var_2) ->
8459	case happyOut303 happy_x_3 of { (HappyWrap303 happy_var_3) ->
8460	case happyOutTok happy_x_4 of { happy_var_4 ->
8461	( ams ((sLL happy_var_1 happy_var_4 $ SigD noExtField (InlineSig noExtField happy_var_3
8462                            (mkInlinePragma (getINLINE_PRAGs happy_var_1) (getINLINE happy_var_1)
8463                                            (snd happy_var_2)))))
8464                       ((mo happy_var_1:fst happy_var_2) ++ [mc happy_var_4]))}}}})
8465	) (\r -> happyReturn (happyIn205 r))
8466
8467happyReduce_487 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8468happyReduce_487 = happyMonadReduce 3# 189# happyReduction_487
8469happyReduction_487 (happy_x_3 `HappyStk`
8470	happy_x_2 `HappyStk`
8471	happy_x_1 `HappyStk`
8472	happyRest) tk
8473	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8474	case happyOut303 happy_x_2 of { (HappyWrap303 happy_var_2) ->
8475	case happyOutTok happy_x_3 of { happy_var_3 ->
8476	( ams (sLL happy_var_1 happy_var_3 (SigD noExtField (SCCFunSig noExtField (getSCC_PRAGs happy_var_1) happy_var_2 Nothing)))
8477                 [mo happy_var_1, mc happy_var_3])}}})
8478	) (\r -> happyReturn (happyIn205 r))
8479
8480happyReduce_488 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8481happyReduce_488 = happyMonadReduce 4# 189# happyReduction_488
8482happyReduction_488 (happy_x_4 `HappyStk`
8483	happy_x_3 `HappyStk`
8484	happy_x_2 `HappyStk`
8485	happy_x_1 `HappyStk`
8486	happyRest) tk
8487	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8488	case happyOut303 happy_x_2 of { (HappyWrap303 happy_var_2) ->
8489	case happyOutTok happy_x_3 of { happy_var_3 ->
8490	case happyOutTok happy_x_4 of { happy_var_4 ->
8491	( do { scc <- getSCC happy_var_3
8492                ; let str_lit = StringLiteral (getSTRINGs happy_var_3) scc
8493                ; ams (sLL happy_var_1 happy_var_4 (SigD noExtField (SCCFunSig noExtField (getSCC_PRAGs happy_var_1) happy_var_2 (Just ( sL1 happy_var_3 str_lit)))))
8494                      [mo happy_var_1, mc happy_var_4] })}}}})
8495	) (\r -> happyReturn (happyIn205 r))
8496
8497happyReduce_489 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8498happyReduce_489 = happyMonadReduce 6# 189# happyReduction_489
8499happyReduction_489 (happy_x_6 `HappyStk`
8500	happy_x_5 `HappyStk`
8501	happy_x_4 `HappyStk`
8502	happy_x_3 `HappyStk`
8503	happy_x_2 `HappyStk`
8504	happy_x_1 `HappyStk`
8505	happyRest) tk
8506	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8507	case happyOut206 happy_x_2 of { (HappyWrap206 happy_var_2) ->
8508	case happyOut303 happy_x_3 of { (HappyWrap303 happy_var_3) ->
8509	case happyOutTok happy_x_4 of { happy_var_4 ->
8510	case happyOut152 happy_x_5 of { (HappyWrap152 happy_var_5) ->
8511	case happyOutTok happy_x_6 of { happy_var_6 ->
8512	( ams (
8513                 let inl_prag = mkInlinePragma (getSPEC_PRAGs happy_var_1)
8514                                             (NoUserInline, FunLike) (snd happy_var_2)
8515                  in sLL happy_var_1 happy_var_6 $ SigD noExtField (SpecSig noExtField happy_var_3 (fromOL happy_var_5) inl_prag))
8516                    (mo happy_var_1:mu AnnDcolon happy_var_4:mc happy_var_6:(fst happy_var_2)))}}}}}})
8517	) (\r -> happyReturn (happyIn205 r))
8518
8519happyReduce_490 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8520happyReduce_490 = happyMonadReduce 6# 189# happyReduction_490
8521happyReduction_490 (happy_x_6 `HappyStk`
8522	happy_x_5 `HappyStk`
8523	happy_x_4 `HappyStk`
8524	happy_x_3 `HappyStk`
8525	happy_x_2 `HappyStk`
8526	happy_x_1 `HappyStk`
8527	happyRest) tk
8528	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8529	case happyOut206 happy_x_2 of { (HappyWrap206 happy_var_2) ->
8530	case happyOut303 happy_x_3 of { (HappyWrap303 happy_var_3) ->
8531	case happyOutTok happy_x_4 of { happy_var_4 ->
8532	case happyOut152 happy_x_5 of { (HappyWrap152 happy_var_5) ->
8533	case happyOutTok happy_x_6 of { happy_var_6 ->
8534	( ams (sLL happy_var_1 happy_var_6 $ SigD noExtField (SpecSig noExtField happy_var_3 (fromOL happy_var_5)
8535                               (mkInlinePragma (getSPEC_INLINE_PRAGs happy_var_1)
8536                                               (getSPEC_INLINE happy_var_1) (snd happy_var_2))))
8537                       (mo happy_var_1:mu AnnDcolon happy_var_4:mc happy_var_6:(fst happy_var_2)))}}}}}})
8538	) (\r -> happyReturn (happyIn205 r))
8539
8540happyReduce_491 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8541happyReduce_491 = happyMonadReduce 4# 189# happyReduction_491
8542happyReduction_491 (happy_x_4 `HappyStk`
8543	happy_x_3 `HappyStk`
8544	happy_x_2 `HappyStk`
8545	happy_x_1 `HappyStk`
8546	happyRest) tk
8547	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8548	case happyOutTok happy_x_2 of { happy_var_2 ->
8549	case happyOut170 happy_x_3 of { (HappyWrap170 happy_var_3) ->
8550	case happyOutTok happy_x_4 of { happy_var_4 ->
8551	( ams (sLL happy_var_1 happy_var_4
8552                                  $ SigD noExtField (SpecInstSig noExtField (getSPEC_PRAGs happy_var_1) happy_var_3))
8553                       [mo happy_var_1,mj AnnInstance happy_var_2,mc happy_var_4])}}}})
8554	) (\r -> happyReturn (happyIn205 r))
8555
8556happyReduce_492 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8557happyReduce_492 = happyMonadReduce 3# 189# happyReduction_492
8558happyReduction_492 (happy_x_3 `HappyStk`
8559	happy_x_2 `HappyStk`
8560	happy_x_1 `HappyStk`
8561	happyRest) tk
8562	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8563	case happyOut266 happy_x_2 of { (HappyWrap266 happy_var_2) ->
8564	case happyOutTok happy_x_3 of { happy_var_3 ->
8565	( ams (sLL happy_var_1 happy_var_3 $ SigD noExtField (MinimalSig noExtField (getMINIMAL_PRAGs happy_var_1) happy_var_2))
8566                   [mo happy_var_1,mc happy_var_3])}}})
8567	) (\r -> happyReturn (happyIn205 r))
8568
8569happyReduce_493 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8570happyReduce_493 = happySpecReduce_0  190# happyReduction_493
8571happyReduction_493  =  happyIn206
8572		 (([],Nothing)
8573	)
8574
8575happyReduce_494 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8576happyReduce_494 = happySpecReduce_1  190# happyReduction_494
8577happyReduction_494 happy_x_1
8578	 =  case happyOut207 happy_x_1 of { (HappyWrap207 happy_var_1) ->
8579	happyIn206
8580		 ((fst happy_var_1,Just (snd happy_var_1))
8581	)}
8582
8583happyReduce_495 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8584happyReduce_495 = happySpecReduce_3  191# happyReduction_495
8585happyReduction_495 happy_x_3
8586	happy_x_2
8587	happy_x_1
8588	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8589	case happyOutTok happy_x_2 of { happy_var_2 ->
8590	case happyOutTok happy_x_3 of { happy_var_3 ->
8591	happyIn207
8592		 (([mj AnnOpenS happy_var_1,mj AnnVal happy_var_2,mj AnnCloseS happy_var_3]
8593                                  ,ActiveAfter  (getINTEGERs happy_var_2) (fromInteger (il_value (getINTEGER happy_var_2))))
8594	)}}}
8595
8596happyReduce_496 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8597happyReduce_496 = happyReduce 4# 191# happyReduction_496
8598happyReduction_496 (happy_x_4 `HappyStk`
8599	happy_x_3 `HappyStk`
8600	happy_x_2 `HappyStk`
8601	happy_x_1 `HappyStk`
8602	happyRest)
8603	 = case happyOutTok happy_x_1 of { happy_var_1 ->
8604	case happyOutTok happy_x_2 of { happy_var_2 ->
8605	case happyOutTok happy_x_3 of { happy_var_3 ->
8606	case happyOutTok happy_x_4 of { happy_var_4 ->
8607	happyIn207
8608		 (([mj AnnOpenS happy_var_1,mj AnnTilde happy_var_2,mj AnnVal happy_var_3
8609                                                 ,mj AnnCloseS happy_var_4]
8610                                  ,ActiveBefore (getINTEGERs happy_var_3) (fromInteger (il_value (getINTEGER happy_var_3))))
8611	) `HappyStk` happyRest}}}}
8612
8613happyReduce_497 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8614happyReduce_497 = happySpecReduce_1  192# happyReduction_497
8615happyReduction_497 happy_x_1
8616	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8617	happyIn208
8618		 (let { loc = getLoc happy_var_1
8619                                ; ITquasiQuote (quoter, quote, quoteSpan) = unLoc happy_var_1
8620                                ; quoterId = mkUnqual varName quoter }
8621                            in sL1 happy_var_1 (mkHsQuasiQuote quoterId (RealSrcSpan quoteSpan) quote)
8622	)}
8623
8624happyReduce_498 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8625happyReduce_498 = happySpecReduce_1  192# happyReduction_498
8626happyReduction_498 happy_x_1
8627	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8628	happyIn208
8629		 (let { loc = getLoc happy_var_1
8630                                ; ITqQuasiQuote (qual, quoter, quote, quoteSpan) = unLoc happy_var_1
8631                                ; quoterId = mkQual varName (qual, quoter) }
8632                            in sL (getLoc happy_var_1) (mkHsQuasiQuote quoterId (RealSrcSpan quoteSpan) quote)
8633	)}
8634
8635happyReduce_499 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8636happyReduce_499 = happySpecReduce_3  193# happyReduction_499
8637happyReduction_499 happy_x_3
8638	happy_x_2
8639	happy_x_1
8640	 =  case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8641	case happyOutTok happy_x_2 of { happy_var_2 ->
8642	case happyOut149 happy_x_3 of { (HappyWrap149 happy_var_3) ->
8643	happyIn209
8644		 (ECP $
8645                                   runECP_PV happy_var_1 >>= \ happy_var_1 ->
8646                                   amms (mkHsTySigPV (comb2 happy_var_1 happy_var_3) happy_var_1 happy_var_3)
8647                                       [mu AnnDcolon happy_var_2]
8648	)}}}
8649
8650happyReduce_500 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8651happyReduce_500 = happyMonadReduce 3# 193# happyReduction_500
8652happyReduction_500 (happy_x_3 `HappyStk`
8653	happy_x_2 `HappyStk`
8654	happy_x_1 `HappyStk`
8655	happyRest) tk
8656	 = happyThen ((case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8657	case happyOutTok happy_x_2 of { happy_var_2 ->
8658	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
8659	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8660                                   runECP_P happy_var_3 >>= \ happy_var_3 ->
8661                                   fmap ecpFromCmd $
8662                                   ams (sLL happy_var_1 happy_var_3 $ HsCmdArrApp noExtField happy_var_1 happy_var_3
8663                                                        HsFirstOrderApp True)
8664                                       [mu Annlarrowtail happy_var_2])}}})
8665	) (\r -> happyReturn (happyIn209 r))
8666
8667happyReduce_501 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8668happyReduce_501 = happyMonadReduce 3# 193# happyReduction_501
8669happyReduction_501 (happy_x_3 `HappyStk`
8670	happy_x_2 `HappyStk`
8671	happy_x_1 `HappyStk`
8672	happyRest) tk
8673	 = happyThen ((case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8674	case happyOutTok happy_x_2 of { happy_var_2 ->
8675	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
8676	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8677                                   runECP_P happy_var_3 >>= \ happy_var_3 ->
8678                                   fmap ecpFromCmd $
8679                                   ams (sLL happy_var_1 happy_var_3 $ HsCmdArrApp noExtField happy_var_3 happy_var_1
8680                                                      HsFirstOrderApp False)
8681                                       [mu Annrarrowtail happy_var_2])}}})
8682	) (\r -> happyReturn (happyIn209 r))
8683
8684happyReduce_502 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8685happyReduce_502 = happyMonadReduce 3# 193# happyReduction_502
8686happyReduction_502 (happy_x_3 `HappyStk`
8687	happy_x_2 `HappyStk`
8688	happy_x_1 `HappyStk`
8689	happyRest) tk
8690	 = happyThen ((case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8691	case happyOutTok happy_x_2 of { happy_var_2 ->
8692	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
8693	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8694                                   runECP_P happy_var_3 >>= \ happy_var_3 ->
8695                                   fmap ecpFromCmd $
8696                                   ams (sLL happy_var_1 happy_var_3 $ HsCmdArrApp noExtField happy_var_1 happy_var_3
8697                                                      HsHigherOrderApp True)
8698                                       [mu AnnLarrowtail happy_var_2])}}})
8699	) (\r -> happyReturn (happyIn209 r))
8700
8701happyReduce_503 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8702happyReduce_503 = happyMonadReduce 3# 193# happyReduction_503
8703happyReduction_503 (happy_x_3 `HappyStk`
8704	happy_x_2 `HappyStk`
8705	happy_x_1 `HappyStk`
8706	happyRest) tk
8707	 = happyThen ((case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8708	case happyOutTok happy_x_2 of { happy_var_2 ->
8709	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
8710	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8711                                   runECP_P happy_var_3 >>= \ happy_var_3 ->
8712                                   fmap ecpFromCmd $
8713                                   ams (sLL happy_var_1 happy_var_3 $ HsCmdArrApp noExtField happy_var_3 happy_var_1
8714                                                      HsHigherOrderApp False)
8715                                       [mu AnnRarrowtail happy_var_2])}}})
8716	) (\r -> happyReturn (happyIn209 r))
8717
8718happyReduce_504 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8719happyReduce_504 = happySpecReduce_1  193# happyReduction_504
8720happyReduction_504 happy_x_1
8721	 =  case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8722	happyIn209
8723		 (happy_var_1
8724	)}
8725
8726happyReduce_505 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8727happyReduce_505 = happySpecReduce_1  194# happyReduction_505
8728happyReduction_505 happy_x_1
8729	 =  case happyOut213 happy_x_1 of { (HappyWrap213 happy_var_1) ->
8730	happyIn210
8731		 (happy_var_1
8732	)}
8733
8734happyReduce_506 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8735happyReduce_506 = happySpecReduce_3  194# happyReduction_506
8736happyReduction_506 happy_x_3
8737	happy_x_2
8738	happy_x_1
8739	 =  case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
8740	case happyOut294 happy_x_2 of { (HappyWrap294 happy_var_2) ->
8741	case happyOut213 happy_x_3 of { (HappyWrap213 happy_var_3) ->
8742	happyIn210
8743		 (ECP $
8744                                 superInfixOp $
8745                                 happy_var_2 >>= \ happy_var_2 ->
8746                                 runECP_PV happy_var_1 >>= \ happy_var_1 ->
8747                                 runECP_PV happy_var_3 >>= \ happy_var_3 ->
8748                                 amms (mkHsOpAppPV (comb2 happy_var_1 happy_var_3) happy_var_1 happy_var_2 happy_var_3)
8749                                     [mj AnnVal happy_var_2]
8750	)}}}
8751
8752happyReduce_507 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8753happyReduce_507 = happySpecReduce_1  195# happyReduction_507
8754happyReduction_507 happy_x_1
8755	 =  case happyOut212 happy_x_1 of { (HappyWrap212 happy_var_1) ->
8756	happyIn211
8757		 (happy_var_1
8758	)}
8759
8760happyReduce_508 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8761happyReduce_508 = happySpecReduce_3  195# happyReduction_508
8762happyReduction_508 happy_x_3
8763	happy_x_2
8764	happy_x_1
8765	 =  case happyOut211 happy_x_1 of { (HappyWrap211 happy_var_1) ->
8766	case happyOut294 happy_x_2 of { (HappyWrap294 happy_var_2) ->
8767	case happyOut212 happy_x_3 of { (HappyWrap212 happy_var_3) ->
8768	happyIn211
8769		 (ECP $
8770                                         superInfixOp $
8771                                         happy_var_2 >>= \ happy_var_2 ->
8772                                         runECP_PV happy_var_1 >>= \ happy_var_1 ->
8773                                         runECP_PV happy_var_3 >>= \ happy_var_3 ->
8774                                         amms (mkHsOpAppPV (comb2 happy_var_1 happy_var_3) happy_var_1 happy_var_2 happy_var_3)
8775                                              [mj AnnVal happy_var_2]
8776	)}}}
8777
8778happyReduce_509 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8779happyReduce_509 = happySpecReduce_2  196# happyReduction_509
8780happyReduction_509 happy_x_2
8781	happy_x_1
8782	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8783	case happyOut217 happy_x_2 of { (HappyWrap217 happy_var_2) ->
8784	happyIn212
8785		 (ECP $
8786                                           runECP_PV happy_var_2 >>= \ happy_var_2 ->
8787                                           amms (mkHsNegAppPV (comb2 happy_var_1 happy_var_2) happy_var_2)
8788                                               [mj AnnMinus happy_var_1]
8789	)}}
8790
8791happyReduce_510 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8792happyReduce_510 = happyMonadReduce 2# 196# happyReduction_510
8793happyReduction_510 (happy_x_2 `HappyStk`
8794	happy_x_1 `HappyStk`
8795	happyRest) tk
8796	 = happyThen ((case happyOut216 happy_x_1 of { (HappyWrap216 happy_var_1) ->
8797	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
8798	( runECP_P happy_var_2 >>= \ happy_var_2 ->
8799                                  fmap ecpFromExp $
8800                                  ams (sLL happy_var_1 happy_var_2 $ HsTickPragma noExtField (snd $ fst $ fst $ unLoc happy_var_1)
8801                                                                (snd $ fst $ unLoc happy_var_1) (snd $ unLoc happy_var_1) happy_var_2)
8802                                      (fst $ fst $ fst $ unLoc happy_var_1))}})
8803	) (\r -> happyReturn (happyIn212 r))
8804
8805happyReduce_511 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8806happyReduce_511 = happyMonadReduce 4# 196# happyReduction_511
8807happyReduction_511 (happy_x_4 `HappyStk`
8808	happy_x_3 `HappyStk`
8809	happy_x_2 `HappyStk`
8810	happy_x_1 `HappyStk`
8811	happyRest) tk
8812	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8813	case happyOutTok happy_x_2 of { happy_var_2 ->
8814	case happyOutTok happy_x_3 of { happy_var_3 ->
8815	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
8816	( runECP_P happy_var_4 >>= \ happy_var_4 ->
8817                                          fmap ecpFromExp $
8818                                          ams (sLL happy_var_1 happy_var_4 $ HsCoreAnn noExtField (getCORE_PRAGs happy_var_1) (getStringLiteral happy_var_2) happy_var_4)
8819                                              [mo happy_var_1,mj AnnVal happy_var_2
8820                                              ,mc happy_var_3])}}}})
8821	) (\r -> happyReturn (happyIn212 r))
8822
8823happyReduce_512 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8824happyReduce_512 = happySpecReduce_1  196# happyReduction_512
8825happyReduction_512 happy_x_1
8826	 =  case happyOut217 happy_x_1 of { (HappyWrap217 happy_var_1) ->
8827	happyIn212
8828		 (happy_var_1
8829	)}
8830
8831happyReduce_513 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8832happyReduce_513 = happySpecReduce_1  197# happyReduction_513
8833happyReduction_513 happy_x_1
8834	 =  case happyOut212 happy_x_1 of { (HappyWrap212 happy_var_1) ->
8835	happyIn213
8836		 (happy_var_1
8837	)}
8838
8839happyReduce_514 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8840happyReduce_514 = happyMonadReduce 2# 197# happyReduction_514
8841happyReduction_514 (happy_x_2 `HappyStk`
8842	happy_x_1 `HappyStk`
8843	happyRest) tk
8844	 = happyThen ((case happyOut215 happy_x_1 of { (HappyWrap215 happy_var_1) ->
8845	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
8846	( runECP_P happy_var_2 >>= \ happy_var_2 ->
8847                                  fmap ecpFromExp $
8848                                  ams (sLL happy_var_1 happy_var_2 $ HsSCC noExtField (snd $ fst $ unLoc happy_var_1) (snd $ unLoc happy_var_1) happy_var_2)
8849                                      (fst $ fst $ unLoc happy_var_1))}})
8850	) (\r -> happyReturn (happyIn213 r))
8851
8852happyReduce_515 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8853happyReduce_515 = happySpecReduce_1  198# happyReduction_515
8854happyReduction_515 happy_x_1
8855	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8856	happyIn214
8857		 (([happy_var_1],True)
8858	)}
8859
8860happyReduce_516 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8861happyReduce_516 = happySpecReduce_0  198# happyReduction_516
8862happyReduction_516  =  happyIn214
8863		 (([],False)
8864	)
8865
8866happyReduce_517 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8867happyReduce_517 = happyMonadReduce 3# 199# happyReduction_517
8868happyReduction_517 (happy_x_3 `HappyStk`
8869	happy_x_2 `HappyStk`
8870	happy_x_1 `HappyStk`
8871	happyRest) tk
8872	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8873	case happyOutTok happy_x_2 of { happy_var_2 ->
8874	case happyOutTok happy_x_3 of { happy_var_3 ->
8875	( do scc <- getSCC happy_var_2
8876                                            ; return $ sLL happy_var_1 happy_var_3
8877                                               (([mo happy_var_1,mj AnnValStr happy_var_2
8878                                                ,mc happy_var_3],getSCC_PRAGs happy_var_1),(StringLiteral (getSTRINGs happy_var_2) scc)))}}})
8879	) (\r -> happyReturn (happyIn215 r))
8880
8881happyReduce_518 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8882happyReduce_518 = happySpecReduce_3  199# happyReduction_518
8883happyReduction_518 happy_x_3
8884	happy_x_2
8885	happy_x_1
8886	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
8887	case happyOutTok happy_x_2 of { happy_var_2 ->
8888	case happyOutTok happy_x_3 of { happy_var_3 ->
8889	happyIn215
8890		 (sLL happy_var_1 happy_var_3 (([mo happy_var_1,mj AnnVal happy_var_2
8891                                         ,mc happy_var_3],getSCC_PRAGs happy_var_1)
8892                                        ,(StringLiteral NoSourceText (getVARID happy_var_2)))
8893	)}}}
8894
8895happyReduce_519 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8896happyReduce_519 = happyReduce 10# 200# happyReduction_519
8897happyReduction_519 (happy_x_10 `HappyStk`
8898	happy_x_9 `HappyStk`
8899	happy_x_8 `HappyStk`
8900	happy_x_7 `HappyStk`
8901	happy_x_6 `HappyStk`
8902	happy_x_5 `HappyStk`
8903	happy_x_4 `HappyStk`
8904	happy_x_3 `HappyStk`
8905	happy_x_2 `HappyStk`
8906	happy_x_1 `HappyStk`
8907	happyRest)
8908	 = case happyOutTok happy_x_1 of { happy_var_1 ->
8909	case happyOutTok happy_x_2 of { happy_var_2 ->
8910	case happyOutTok happy_x_3 of { happy_var_3 ->
8911	case happyOutTok happy_x_4 of { happy_var_4 ->
8912	case happyOutTok happy_x_5 of { happy_var_5 ->
8913	case happyOutTok happy_x_6 of { happy_var_6 ->
8914	case happyOutTok happy_x_7 of { happy_var_7 ->
8915	case happyOutTok happy_x_8 of { happy_var_8 ->
8916	case happyOutTok happy_x_9 of { happy_var_9 ->
8917	case happyOutTok happy_x_10 of { happy_var_10 ->
8918	happyIn216
8919		 (sLL happy_var_1 happy_var_10 $ ((([mo happy_var_1,mj AnnVal happy_var_2
8920                                              ,mj AnnVal happy_var_3,mj AnnColon happy_var_4
8921                                              ,mj AnnVal happy_var_5,mj AnnMinus happy_var_6
8922                                              ,mj AnnVal happy_var_7,mj AnnColon happy_var_8
8923                                              ,mj AnnVal happy_var_9,mc happy_var_10],
8924                                                getGENERATED_PRAGs happy_var_1)
8925                                              ,((getStringLiteral happy_var_2)
8926                                               ,( fromInteger $ il_value $ getINTEGER happy_var_3
8927                                                , fromInteger $ il_value $ getINTEGER happy_var_5
8928                                                )
8929                                               ,( fromInteger $ il_value $ getINTEGER happy_var_7
8930                                                , fromInteger $ il_value $ getINTEGER happy_var_9
8931                                                )
8932                                               ))
8933                                             , (( getINTEGERs happy_var_3
8934                                                , getINTEGERs happy_var_5
8935                                                )
8936                                               ,( getINTEGERs happy_var_7
8937                                                , getINTEGERs happy_var_9
8938                                                )))
8939	) `HappyStk` happyRest}}}}}}}}}}
8940
8941happyReduce_520 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8942happyReduce_520 = happySpecReduce_2  201# happyReduction_520
8943happyReduction_520 happy_x_2
8944	happy_x_1
8945	 =  case happyOut217 happy_x_1 of { (HappyWrap217 happy_var_1) ->
8946	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
8947	happyIn217
8948		 (ECP $
8949                                          superFunArg $
8950                                          runECP_PV happy_var_1 >>= \ happy_var_1 ->
8951                                          runECP_PV happy_var_2 >>= \ happy_var_2 ->
8952                                          mkHsAppPV (comb2 happy_var_1 happy_var_2) happy_var_1 happy_var_2
8953	)}}
8954
8955happyReduce_521 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8956happyReduce_521 = happyMonadReduce 3# 201# happyReduction_521
8957happyReduction_521 (happy_x_3 `HappyStk`
8958	happy_x_2 `HappyStk`
8959	happy_x_1 `HappyStk`
8960	happyRest) tk
8961	 = happyThen ((case happyOut217 happy_x_1 of { (HappyWrap217 happy_var_1) ->
8962	case happyOutTok happy_x_2 of { happy_var_2 ->
8963	case happyOut169 happy_x_3 of { (HappyWrap169 happy_var_3) ->
8964	( runECP_P happy_var_1 >>= \ happy_var_1 ->
8965                                        runPV (checkExpBlockArguments happy_var_1) >>= \_ ->
8966                                        fmap ecpFromExp $
8967                                        ams (sLL happy_var_1 happy_var_3 $ HsAppType noExtField happy_var_1 (mkHsWildCardBndrs happy_var_3))
8968                                            [mj AnnAt happy_var_2])}}})
8969	) (\r -> happyReturn (happyIn217 r))
8970
8971happyReduce_522 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8972happyReduce_522 = happyMonadReduce 2# 201# happyReduction_522
8973happyReduction_522 (happy_x_2 `HappyStk`
8974	happy_x_1 `HappyStk`
8975	happyRest) tk
8976	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
8977	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
8978	( runECP_P happy_var_2 >>= \ happy_var_2 ->
8979                                        fmap ecpFromExp $
8980                                        ams (sLL happy_var_1 happy_var_2 $ HsStatic noExtField happy_var_2)
8981                                            [mj AnnStatic happy_var_1])}})
8982	) (\r -> happyReturn (happyIn217 r))
8983
8984happyReduce_523 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8985happyReduce_523 = happySpecReduce_1  201# happyReduction_523
8986happyReduction_523 happy_x_1
8987	 =  case happyOut218 happy_x_1 of { (HappyWrap218 happy_var_1) ->
8988	happyIn217
8989		 (happy_var_1
8990	)}
8991
8992happyReduce_524 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
8993happyReduce_524 = happySpecReduce_3  202# happyReduction_524
8994happyReduction_524 happy_x_3
8995	happy_x_2
8996	happy_x_1
8997	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
8998	case happyOutTok happy_x_2 of { happy_var_2 ->
8999	case happyOut218 happy_x_3 of { (HappyWrap218 happy_var_3) ->
9000	happyIn218
9001		 (ECP $
9002                                   runECP_PV happy_var_3 >>= \ happy_var_3 ->
9003                                   amms (mkHsAsPatPV (comb2 happy_var_1 happy_var_3) happy_var_1 happy_var_3) [mj AnnAt happy_var_2]
9004	)}}}
9005
9006happyReduce_525 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9007happyReduce_525 = happySpecReduce_2  202# happyReduction_525
9008happyReduction_525 happy_x_2
9009	happy_x_1
9010	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9011	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
9012	happyIn218
9013		 (ECP $
9014                                   runECP_PV happy_var_2 >>= \ happy_var_2 ->
9015                                   amms (mkHsLazyPatPV (comb2 happy_var_1 happy_var_2) happy_var_2) [mj AnnTilde happy_var_1]
9016	)}}
9017
9018happyReduce_526 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9019happyReduce_526 = happyReduce 5# 202# happyReduction_526
9020happyReduction_526 (happy_x_5 `HappyStk`
9021	happy_x_4 `HappyStk`
9022	happy_x_3 `HappyStk`
9023	happy_x_2 `HappyStk`
9024	happy_x_1 `HappyStk`
9025	happyRest)
9026	 = case happyOutTok happy_x_1 of { happy_var_1 ->
9027	case happyOut251 happy_x_2 of { (HappyWrap251 happy_var_2) ->
9028	case happyOut252 happy_x_3 of { (HappyWrap252 happy_var_3) ->
9029	case happyOutTok happy_x_4 of { happy_var_4 ->
9030	case happyOut209 happy_x_5 of { (HappyWrap209 happy_var_5) ->
9031	happyIn218
9032		 (ECP $
9033                      runECP_PV happy_var_5 >>= \ happy_var_5 ->
9034                      amms (mkHsLamPV (comb2 happy_var_1 happy_var_5) (mkMatchGroup FromSource
9035                            [sLL happy_var_1 happy_var_5 $ Match { m_ext = noExtField
9036                                               , m_ctxt = LambdaExpr
9037                                               , m_pats = happy_var_2:happy_var_3
9038                                               , m_grhss = unguardedGRHSs happy_var_5 }]))
9039                          [mj AnnLam happy_var_1, mu AnnRarrow happy_var_4]
9040	) `HappyStk` happyRest}}}}}
9041
9042happyReduce_527 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9043happyReduce_527 = happyReduce 4# 202# happyReduction_527
9044happyReduction_527 (happy_x_4 `HappyStk`
9045	happy_x_3 `HappyStk`
9046	happy_x_2 `HappyStk`
9047	happy_x_1 `HappyStk`
9048	happyRest)
9049	 = case happyOutTok happy_x_1 of { happy_var_1 ->
9050	case happyOut127 happy_x_2 of { (HappyWrap127 happy_var_2) ->
9051	case happyOutTok happy_x_3 of { happy_var_3 ->
9052	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
9053	happyIn218
9054		 (ECP $
9055                                           runECP_PV happy_var_4 >>= \ happy_var_4 ->
9056                                           amms (mkHsLetPV (comb2 happy_var_1 happy_var_4) (snd (unLoc happy_var_2)) happy_var_4)
9057                                               (mj AnnLet happy_var_1:mj AnnIn happy_var_3
9058                                                 :(fst $ unLoc happy_var_2))
9059	) `HappyStk` happyRest}}}}
9060
9061happyReduce_528 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9062happyReduce_528 = happyMonadReduce 3# 202# happyReduction_528
9063happyReduction_528 (happy_x_3 `HappyStk`
9064	happy_x_2 `HappyStk`
9065	happy_x_1 `HappyStk`
9066	happyRest) tk
9067	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9068	case happyOutTok happy_x_2 of { happy_var_2 ->
9069	case happyOut240 happy_x_3 of { (HappyWrap240 happy_var_3) ->
9070	( runPV happy_var_3 >>= \ happy_var_3 ->
9071               fmap ecpFromExp $
9072               ams (sLL happy_var_1 happy_var_3 $ HsLamCase noExtField
9073                                   (mkMatchGroup FromSource (snd $ unLoc happy_var_3)))
9074                   (mj AnnLam happy_var_1:mj AnnCase happy_var_2:(fst $ unLoc happy_var_3)))}}})
9075	) (\r -> happyReturn (happyIn218 r))
9076
9077happyReduce_529 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9078happyReduce_529 = happyMonadReduce 8# 202# happyReduction_529
9079happyReduction_529 (happy_x_8 `HappyStk`
9080	happy_x_7 `HappyStk`
9081	happy_x_6 `HappyStk`
9082	happy_x_5 `HappyStk`
9083	happy_x_4 `HappyStk`
9084	happy_x_3 `HappyStk`
9085	happy_x_2 `HappyStk`
9086	happy_x_1 `HappyStk`
9087	happyRest) tk
9088	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9089	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9090	case happyOut214 happy_x_3 of { (HappyWrap214 happy_var_3) ->
9091	case happyOutTok happy_x_4 of { happy_var_4 ->
9092	case happyOut209 happy_x_5 of { (HappyWrap209 happy_var_5) ->
9093	case happyOut214 happy_x_6 of { (HappyWrap214 happy_var_6) ->
9094	case happyOutTok happy_x_7 of { happy_var_7 ->
9095	case happyOut209 happy_x_8 of { (HappyWrap209 happy_var_8) ->
9096	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9097                            return $ ECP $
9098                              runECP_PV happy_var_5 >>= \ happy_var_5 ->
9099                              runECP_PV happy_var_8 >>= \ happy_var_8 ->
9100                              amms (mkHsIfPV (comb2 happy_var_1 happy_var_8) happy_var_2 (snd happy_var_3) happy_var_5 (snd happy_var_6) happy_var_8)
9101                                  (mj AnnIf happy_var_1:mj AnnThen happy_var_4
9102                                     :mj AnnElse happy_var_7
9103                                     :(map (\l -> mj AnnSemi l) (fst happy_var_3))
9104                                    ++(map (\l -> mj AnnSemi l) (fst happy_var_6))))}}}}}}}})
9105	) (\r -> happyReturn (happyIn218 r))
9106
9107happyReduce_530 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9108happyReduce_530 = happyMonadReduce 2# 202# happyReduction_530
9109happyReduction_530 (happy_x_2 `HappyStk`
9110	happy_x_1 `HappyStk`
9111	happyRest) tk
9112	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9113	case happyOut247 happy_x_2 of { (HappyWrap247 happy_var_2) ->
9114	( hintMultiWayIf (getLoc happy_var_1) >>= \_ ->
9115                                           fmap ecpFromExp $
9116                                           ams (sLL happy_var_1 happy_var_2 $ HsMultiIf noExtField
9117                                                     (reverse $ snd $ unLoc happy_var_2))
9118                                               (mj AnnIf happy_var_1:(fst $ unLoc happy_var_2)))}})
9119	) (\r -> happyReturn (happyIn218 r))
9120
9121happyReduce_531 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9122happyReduce_531 = happyMonadReduce 4# 202# happyReduction_531
9123happyReduction_531 (happy_x_4 `HappyStk`
9124	happy_x_3 `HappyStk`
9125	happy_x_2 `HappyStk`
9126	happy_x_1 `HappyStk`
9127	happyRest) tk
9128	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9129	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9130	case happyOutTok happy_x_3 of { happy_var_3 ->
9131	case happyOut240 happy_x_4 of { (HappyWrap240 happy_var_4) ->
9132	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9133                                         return $ ECP $
9134                                           happy_var_4 >>= \ happy_var_4 ->
9135                                           amms (mkHsCasePV (comb3 happy_var_1 happy_var_3 happy_var_4) happy_var_2 (mkMatchGroup
9136                                                   FromSource (snd $ unLoc happy_var_4)))
9137                                               (mj AnnCase happy_var_1:mj AnnOf happy_var_3
9138                                                  :(fst $ unLoc happy_var_4)))}}}})
9139	) (\r -> happyReturn (happyIn218 r))
9140
9141happyReduce_532 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9142happyReduce_532 = happySpecReduce_2  202# happyReduction_532
9143happyReduction_532 happy_x_2
9144	happy_x_1
9145	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9146	case happyOut253 happy_x_2 of { (HappyWrap253 happy_var_2) ->
9147	happyIn218
9148		 (ECP $
9149                                        happy_var_2 >>= \ happy_var_2 ->
9150                                        amms (mkHsDoPV (comb2 happy_var_1 happy_var_2) (mapLoc snd happy_var_2))
9151                                               (mj AnnDo happy_var_1:(fst $ unLoc happy_var_2))
9152	)}}
9153
9154happyReduce_533 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9155happyReduce_533 = happyMonadReduce 2# 202# happyReduction_533
9156happyReduction_533 (happy_x_2 `HappyStk`
9157	happy_x_1 `HappyStk`
9158	happyRest) tk
9159	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9160	case happyOut253 happy_x_2 of { (HappyWrap253 happy_var_2) ->
9161	( runPV happy_var_2 >>= \ happy_var_2 ->
9162                                       fmap ecpFromExp $
9163                                       ams (cL (comb2 happy_var_1 happy_var_2)
9164                                              (mkHsDo MDoExpr (snd $ unLoc happy_var_2)))
9165                                           (mj AnnMdo happy_var_1:(fst $ unLoc happy_var_2)))}})
9166	) (\r -> happyReturn (happyIn218 r))
9167
9168happyReduce_534 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9169happyReduce_534 = happyMonadReduce 4# 202# happyReduction_534
9170happyReduction_534 (happy_x_4 `HappyStk`
9171	happy_x_3 `HappyStk`
9172	happy_x_2 `HappyStk`
9173	happy_x_1 `HappyStk`
9174	happyRest) tk
9175	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9176	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
9177	case happyOutTok happy_x_3 of { happy_var_3 ->
9178	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
9179	( (checkPattern <=< runECP_P) happy_var_2 >>= \ p ->
9180                           runECP_P happy_var_4 >>= \ happy_var_4@cmd ->
9181                           fmap ecpFromExp $
9182                           ams (sLL happy_var_1 happy_var_4 $ HsProc noExtField p (sLL happy_var_1 happy_var_4 $ HsCmdTop noExtField cmd))
9183                                            -- TODO: is LL right here?
9184                               [mj AnnProc happy_var_1,mu AnnRarrow happy_var_3])}}}})
9185	) (\r -> happyReturn (happyIn218 r))
9186
9187happyReduce_535 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9188happyReduce_535 = happySpecReduce_1  202# happyReduction_535
9189happyReduction_535 happy_x_1
9190	 =  case happyOut219 happy_x_1 of { (HappyWrap219 happy_var_1) ->
9191	happyIn218
9192		 (happy_var_1
9193	)}
9194
9195happyReduce_536 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9196happyReduce_536 = happyReduce 4# 203# happyReduction_536
9197happyReduction_536 (happy_x_4 `HappyStk`
9198	happy_x_3 `HappyStk`
9199	happy_x_2 `HappyStk`
9200	happy_x_1 `HappyStk`
9201	happyRest)
9202	 = case happyOut219 happy_x_1 of { (HappyWrap219 happy_var_1) ->
9203	case happyOutTok happy_x_2 of { happy_var_2 ->
9204	case happyOut259 happy_x_3 of { (HappyWrap259 happy_var_3) ->
9205	case happyOutTok happy_x_4 of { happy_var_4 ->
9206	happyIn219
9207		 (ECP $
9208                                  runECP_PV happy_var_1 >>= \ happy_var_1 ->
9209                                  happy_var_3 >>= \ happy_var_3 ->
9210                                  amms (mkHsRecordPV (comb2 happy_var_1 happy_var_4) (comb2 happy_var_2 happy_var_4) happy_var_1 (snd happy_var_3))
9211                                       (moc happy_var_2:mcc happy_var_4:(fst happy_var_3))
9212	) `HappyStk` happyRest}}}}
9213
9214happyReduce_537 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9215happyReduce_537 = happySpecReduce_1  203# happyReduction_537
9216happyReduction_537 happy_x_1
9217	 =  case happyOut220 happy_x_1 of { (HappyWrap220 happy_var_1) ->
9218	happyIn219
9219		 (happy_var_1
9220	)}
9221
9222happyReduce_538 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9223happyReduce_538 = happySpecReduce_1  204# happyReduction_538
9224happyReduction_538 happy_x_1
9225	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
9226	happyIn220
9227		 (ECP $ mkHsVarPV $! happy_var_1
9228	)}
9229
9230happyReduce_539 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9231happyReduce_539 = happySpecReduce_1  204# happyReduction_539
9232happyReduction_539 happy_x_1
9233	 =  case happyOut274 happy_x_1 of { (HappyWrap274 happy_var_1) ->
9234	happyIn220
9235		 (ECP $ mkHsVarPV $! happy_var_1
9236	)}
9237
9238happyReduce_540 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9239happyReduce_540 = happySpecReduce_1  204# happyReduction_540
9240happyReduction_540 happy_x_1
9241	 =  case happyOut264 happy_x_1 of { (HappyWrap264 happy_var_1) ->
9242	happyIn220
9243		 (ecpFromExp $ sL1 happy_var_1 (HsIPVar noExtField $! unLoc happy_var_1)
9244	)}
9245
9246happyReduce_541 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9247happyReduce_541 = happySpecReduce_1  204# happyReduction_541
9248happyReduction_541 happy_x_1
9249	 =  case happyOut265 happy_x_1 of { (HappyWrap265 happy_var_1) ->
9250	happyIn220
9251		 (ecpFromExp $ sL1 happy_var_1 (HsOverLabel noExtField Nothing $! unLoc happy_var_1)
9252	)}
9253
9254happyReduce_542 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9255happyReduce_542 = happySpecReduce_1  204# happyReduction_542
9256happyReduction_542 happy_x_1
9257	 =  case happyOut317 happy_x_1 of { (HappyWrap317 happy_var_1) ->
9258	happyIn220
9259		 (ECP $ mkHsLitPV $! happy_var_1
9260	)}
9261
9262happyReduce_543 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9263happyReduce_543 = happySpecReduce_1  204# happyReduction_543
9264happyReduction_543 happy_x_1
9265	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9266	happyIn220
9267		 (ECP $ mkHsOverLitPV (sL1 happy_var_1 $ mkHsIntegral   (getINTEGER  happy_var_1))
9268	)}
9269
9270happyReduce_544 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9271happyReduce_544 = happySpecReduce_1  204# happyReduction_544
9272happyReduction_544 happy_x_1
9273	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9274	happyIn220
9275		 (ECP $ mkHsOverLitPV (sL1 happy_var_1 $ mkHsFractional (getRATIONAL happy_var_1))
9276	)}
9277
9278happyReduce_545 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9279happyReduce_545 = happySpecReduce_3  204# happyReduction_545
9280happyReduction_545 happy_x_3
9281	happy_x_2
9282	happy_x_1
9283	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9284	case happyOut228 happy_x_2 of { (HappyWrap228 happy_var_2) ->
9285	case happyOutTok happy_x_3 of { happy_var_3 ->
9286	happyIn220
9287		 (ECP $
9288                                           runECP_PV happy_var_2 >>= \ happy_var_2 ->
9289                                           amms (mkHsParPV (comb2 happy_var_1 happy_var_3) happy_var_2) [mop happy_var_1,mcp happy_var_3]
9290	)}}}
9291
9292happyReduce_546 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9293happyReduce_546 = happySpecReduce_3  204# happyReduction_546
9294happyReduction_546 happy_x_3
9295	happy_x_2
9296	happy_x_1
9297	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9298	case happyOut229 happy_x_2 of { (HappyWrap229 happy_var_2) ->
9299	case happyOutTok happy_x_3 of { happy_var_3 ->
9300	happyIn220
9301		 (ECP $
9302                                           happy_var_2 >>= \ happy_var_2 ->
9303                                           amms (mkSumOrTuplePV (comb2 happy_var_1 happy_var_3) Boxed (snd happy_var_2))
9304                                                ((mop happy_var_1:fst happy_var_2) ++ [mcp happy_var_3])
9305	)}}}
9306
9307happyReduce_547 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9308happyReduce_547 = happySpecReduce_3  204# happyReduction_547
9309happyReduction_547 happy_x_3
9310	happy_x_2
9311	happy_x_1
9312	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9313	case happyOut228 happy_x_2 of { (HappyWrap228 happy_var_2) ->
9314	case happyOutTok happy_x_3 of { happy_var_3 ->
9315	happyIn220
9316		 (ECP $
9317                                           runECP_PV happy_var_2 >>= \ happy_var_2 ->
9318                                           amms (mkSumOrTuplePV (comb2 happy_var_1 happy_var_3) Unboxed (Tuple [cL (gl happy_var_2) (Just happy_var_2)]))
9319                                                [mo happy_var_1,mc happy_var_3]
9320	)}}}
9321
9322happyReduce_548 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9323happyReduce_548 = happySpecReduce_3  204# happyReduction_548
9324happyReduction_548 happy_x_3
9325	happy_x_2
9326	happy_x_1
9327	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9328	case happyOut229 happy_x_2 of { (HappyWrap229 happy_var_2) ->
9329	case happyOutTok happy_x_3 of { happy_var_3 ->
9330	happyIn220
9331		 (ECP $
9332                                           happy_var_2 >>= \ happy_var_2 ->
9333                                           amms (mkSumOrTuplePV (comb2 happy_var_1 happy_var_3) Unboxed (snd happy_var_2))
9334                                                ((mo happy_var_1:fst happy_var_2) ++ [mc happy_var_3])
9335	)}}}
9336
9337happyReduce_549 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9338happyReduce_549 = happySpecReduce_3  204# happyReduction_549
9339happyReduction_549 happy_x_3
9340	happy_x_2
9341	happy_x_1
9342	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9343	case happyOut232 happy_x_2 of { (HappyWrap232 happy_var_2) ->
9344	case happyOutTok happy_x_3 of { happy_var_3 ->
9345	happyIn220
9346		 (ECP $ happy_var_2 (comb2 happy_var_1 happy_var_3) >>= \a -> ams a [mos happy_var_1,mcs happy_var_3]
9347	)}}}
9348
9349happyReduce_550 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9350happyReduce_550 = happySpecReduce_1  204# happyReduction_550
9351happyReduction_550 happy_x_1
9352	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9353	happyIn220
9354		 (ECP $ mkHsWildCardPV (getLoc happy_var_1)
9355	)}
9356
9357happyReduce_551 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9358happyReduce_551 = happySpecReduce_1  204# happyReduction_551
9359happyReduction_551 happy_x_1
9360	 =  case happyOut222 happy_x_1 of { (HappyWrap222 happy_var_1) ->
9361	happyIn220
9362		 (ECP $ mkHsSplicePV happy_var_1
9363	)}
9364
9365happyReduce_552 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9366happyReduce_552 = happySpecReduce_1  204# happyReduction_552
9367happyReduction_552 happy_x_1
9368	 =  case happyOut223 happy_x_1 of { (HappyWrap223 happy_var_1) ->
9369	happyIn220
9370		 (ecpFromExp $ mapLoc (HsSpliceE noExtField) happy_var_1
9371	)}
9372
9373happyReduce_553 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9374happyReduce_553 = happyMonadReduce 2# 204# happyReduction_553
9375happyReduction_553 (happy_x_2 `HappyStk`
9376	happy_x_1 `HappyStk`
9377	happyRest) tk
9378	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9379	case happyOut303 happy_x_2 of { (HappyWrap303 happy_var_2) ->
9380	( fmap ecpFromExp $ ams (sLL happy_var_1 happy_var_2 $ HsBracket noExtField (VarBr noExtField True  (unLoc happy_var_2))) [mj AnnSimpleQuote happy_var_1,mj AnnName happy_var_2])}})
9381	) (\r -> happyReturn (happyIn220 r))
9382
9383happyReduce_554 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9384happyReduce_554 = happyMonadReduce 2# 204# happyReduction_554
9385happyReduction_554 (happy_x_2 `HappyStk`
9386	happy_x_1 `HappyStk`
9387	happyRest) tk
9388	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9389	case happyOut274 happy_x_2 of { (HappyWrap274 happy_var_2) ->
9390	( fmap ecpFromExp $ ams (sLL happy_var_1 happy_var_2 $ HsBracket noExtField (VarBr noExtField True  (unLoc happy_var_2))) [mj AnnSimpleQuote happy_var_1,mj AnnName happy_var_2])}})
9391	) (\r -> happyReturn (happyIn220 r))
9392
9393happyReduce_555 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9394happyReduce_555 = happyMonadReduce 2# 204# happyReduction_555
9395happyReduction_555 (happy_x_2 `HappyStk`
9396	happy_x_1 `HappyStk`
9397	happyRest) tk
9398	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9399	case happyOut299 happy_x_2 of { (HappyWrap299 happy_var_2) ->
9400	( fmap ecpFromExp $ ams (sLL happy_var_1 happy_var_2 $ HsBracket noExtField (VarBr noExtField False (unLoc happy_var_2))) [mj AnnThTyQuote happy_var_1,mj AnnName happy_var_2])}})
9401	) (\r -> happyReturn (happyIn220 r))
9402
9403happyReduce_556 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9404happyReduce_556 = happyMonadReduce 2# 204# happyReduction_556
9405happyReduction_556 (happy_x_2 `HappyStk`
9406	happy_x_1 `HappyStk`
9407	happyRest) tk
9408	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9409	case happyOut282 happy_x_2 of { (HappyWrap282 happy_var_2) ->
9410	( fmap ecpFromExp $ ams (sLL happy_var_1 happy_var_2 $ HsBracket noExtField (VarBr noExtField False (unLoc happy_var_2))) [mj AnnThTyQuote happy_var_1,mj AnnName happy_var_2])}})
9411	) (\r -> happyReturn (happyIn220 r))
9412
9413happyReduce_557 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9414happyReduce_557 = happyMonadReduce 1# 204# happyReduction_557
9415happyReduction_557 (happy_x_1 `HappyStk`
9416	happyRest) tk
9417	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9418	( reportEmptyDoubleQuotes (getLoc happy_var_1))})
9419	) (\r -> happyReturn (happyIn220 r))
9420
9421happyReduce_558 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9422happyReduce_558 = happyMonadReduce 3# 204# happyReduction_558
9423happyReduction_558 (happy_x_3 `HappyStk`
9424	happy_x_2 `HappyStk`
9425	happy_x_1 `HappyStk`
9426	happyRest) tk
9427	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9428	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9429	case happyOutTok happy_x_3 of { happy_var_3 ->
9430	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9431                                 fmap ecpFromExp $
9432                                 ams (sLL happy_var_1 happy_var_3 $ HsBracket noExtField (ExpBr noExtField happy_var_2))
9433                                      (if (hasE happy_var_1) then [mj AnnOpenE happy_var_1, mu AnnCloseQ happy_var_3]
9434                                                    else [mu AnnOpenEQ happy_var_1,mu AnnCloseQ happy_var_3]))}}})
9435	) (\r -> happyReturn (happyIn220 r))
9436
9437happyReduce_559 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9438happyReduce_559 = happyMonadReduce 3# 204# happyReduction_559
9439happyReduction_559 (happy_x_3 `HappyStk`
9440	happy_x_2 `HappyStk`
9441	happy_x_1 `HappyStk`
9442	happyRest) tk
9443	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9444	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9445	case happyOutTok happy_x_3 of { happy_var_3 ->
9446	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9447                                 fmap ecpFromExp $
9448                                 ams (sLL happy_var_1 happy_var_3 $ HsBracket noExtField (TExpBr noExtField happy_var_2))
9449                                      (if (hasE happy_var_1) then [mj AnnOpenE happy_var_1,mc happy_var_3] else [mo happy_var_1,mc happy_var_3]))}}})
9450	) (\r -> happyReturn (happyIn220 r))
9451
9452happyReduce_560 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9453happyReduce_560 = happyMonadReduce 3# 204# happyReduction_560
9454happyReduction_560 (happy_x_3 `HappyStk`
9455	happy_x_2 `HappyStk`
9456	happy_x_1 `HappyStk`
9457	happyRest) tk
9458	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9459	case happyOut155 happy_x_2 of { (HappyWrap155 happy_var_2) ->
9460	case happyOutTok happy_x_3 of { happy_var_3 ->
9461	( fmap ecpFromExp $
9462                                 ams (sLL happy_var_1 happy_var_3 $ HsBracket noExtField (TypBr noExtField happy_var_2)) [mo happy_var_1,mu AnnCloseQ happy_var_3])}}})
9463	) (\r -> happyReturn (happyIn220 r))
9464
9465happyReduce_561 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9466happyReduce_561 = happyMonadReduce 3# 204# happyReduction_561
9467happyReduction_561 (happy_x_3 `HappyStk`
9468	happy_x_2 `HappyStk`
9469	happy_x_1 `HappyStk`
9470	happyRest) tk
9471	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9472	case happyOut210 happy_x_2 of { (HappyWrap210 happy_var_2) ->
9473	case happyOutTok happy_x_3 of { happy_var_3 ->
9474	( (checkPattern <=< runECP_P) happy_var_2 >>= \p ->
9475                                      fmap ecpFromExp $
9476                                      ams (sLL happy_var_1 happy_var_3 $ HsBracket noExtField (PatBr noExtField p))
9477                                          [mo happy_var_1,mu AnnCloseQ happy_var_3])}}})
9478	) (\r -> happyReturn (happyIn220 r))
9479
9480happyReduce_562 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9481happyReduce_562 = happyMonadReduce 3# 204# happyReduction_562
9482happyReduction_562 (happy_x_3 `HappyStk`
9483	happy_x_2 `HappyStk`
9484	happy_x_1 `HappyStk`
9485	happyRest) tk
9486	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9487	case happyOut226 happy_x_2 of { (HappyWrap226 happy_var_2) ->
9488	case happyOutTok happy_x_3 of { happy_var_3 ->
9489	( fmap ecpFromExp $
9490                                  ams (sLL happy_var_1 happy_var_3 $ HsBracket noExtField (DecBrL noExtField (snd happy_var_2)))
9491                                      (mo happy_var_1:mu AnnCloseQ happy_var_3:fst happy_var_2))}}})
9492	) (\r -> happyReturn (happyIn220 r))
9493
9494happyReduce_563 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9495happyReduce_563 = happySpecReduce_1  204# happyReduction_563
9496happyReduction_563 happy_x_1
9497	 =  case happyOut208 happy_x_1 of { (HappyWrap208 happy_var_1) ->
9498	happyIn220
9499		 (ECP $ mkHsSplicePV happy_var_1
9500	)}
9501
9502happyReduce_564 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9503happyReduce_564 = happyMonadReduce 4# 204# happyReduction_564
9504happyReduction_564 (happy_x_4 `HappyStk`
9505	happy_x_3 `HappyStk`
9506	happy_x_2 `HappyStk`
9507	happy_x_1 `HappyStk`
9508	happyRest) tk
9509	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9510	case happyOut220 happy_x_2 of { (HappyWrap220 happy_var_2) ->
9511	case happyOut224 happy_x_3 of { (HappyWrap224 happy_var_3) ->
9512	case happyOutTok happy_x_4 of { happy_var_4 ->
9513	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9514                                      fmap ecpFromCmd $
9515                                      ams (sLL happy_var_1 happy_var_4 $ HsCmdArrForm noExtField happy_var_2 Prefix
9516                                                           Nothing (reverse happy_var_3))
9517                                          [mu AnnOpenB happy_var_1,mu AnnCloseB happy_var_4])}}}})
9518	) (\r -> happyReturn (happyIn220 r))
9519
9520happyReduce_565 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9521happyReduce_565 = happySpecReduce_1  205# happyReduction_565
9522happyReduction_565 happy_x_1
9523	 =  case happyOut222 happy_x_1 of { (HappyWrap222 happy_var_1) ->
9524	happyIn221
9525		 (mapLoc (HsSpliceE noExtField) happy_var_1
9526	)}
9527
9528happyReduce_566 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9529happyReduce_566 = happySpecReduce_1  205# happyReduction_566
9530happyReduction_566 happy_x_1
9531	 =  case happyOut223 happy_x_1 of { (HappyWrap223 happy_var_1) ->
9532	happyIn221
9533		 (mapLoc (HsSpliceE noExtField) happy_var_1
9534	)}
9535
9536happyReduce_567 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9537happyReduce_567 = happyMonadReduce 1# 206# happyReduction_567
9538happyReduction_567 (happy_x_1 `HappyStk`
9539	happyRest) tk
9540	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9541	( ams (sL1 happy_var_1 $ mkUntypedSplice HasDollar
9542                                        (sL1 happy_var_1 $ HsVar noExtField (sL1 happy_var_1 (mkUnqual varName
9543                                                           (getTH_ID_SPLICE happy_var_1)))))
9544                                       [mj AnnThIdSplice happy_var_1])})
9545	) (\r -> happyReturn (happyIn222 r))
9546
9547happyReduce_568 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9548happyReduce_568 = happyMonadReduce 3# 206# happyReduction_568
9549happyReduction_568 (happy_x_3 `HappyStk`
9550	happy_x_2 `HappyStk`
9551	happy_x_1 `HappyStk`
9552	happyRest) tk
9553	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9554	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9555	case happyOutTok happy_x_3 of { happy_var_3 ->
9556	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9557                                   ams (sLL happy_var_1 happy_var_3 $ mkUntypedSplice HasParens happy_var_2)
9558                                       [mj AnnOpenPE happy_var_1,mj AnnCloseP happy_var_3])}}})
9559	) (\r -> happyReturn (happyIn222 r))
9560
9561happyReduce_569 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9562happyReduce_569 = happyMonadReduce 1# 207# happyReduction_569
9563happyReduction_569 (happy_x_1 `HappyStk`
9564	happyRest) tk
9565	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9566	( ams (sL1 happy_var_1 $ mkTypedSplice HasDollar
9567                                        (sL1 happy_var_1 $ HsVar noExtField (sL1 happy_var_1 (mkUnqual varName
9568                                                        (getTH_ID_TY_SPLICE happy_var_1)))))
9569                                       [mj AnnThIdTySplice happy_var_1])})
9570	) (\r -> happyReturn (happyIn223 r))
9571
9572happyReduce_570 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9573happyReduce_570 = happyMonadReduce 3# 207# happyReduction_570
9574happyReduction_570 (happy_x_3 `HappyStk`
9575	happy_x_2 `HappyStk`
9576	happy_x_1 `HappyStk`
9577	happyRest) tk
9578	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
9579	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
9580	case happyOutTok happy_x_3 of { happy_var_3 ->
9581	( runECP_P happy_var_2 >>= \ happy_var_2 ->
9582                                    ams (sLL happy_var_1 happy_var_3 $ mkTypedSplice HasParens happy_var_2)
9583                                       [mj AnnOpenPTE happy_var_1,mj AnnCloseP happy_var_3])}}})
9584	) (\r -> happyReturn (happyIn223 r))
9585
9586happyReduce_571 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9587happyReduce_571 = happySpecReduce_2  208# happyReduction_571
9588happyReduction_571 happy_x_2
9589	happy_x_1
9590	 =  case happyOut224 happy_x_1 of { (HappyWrap224 happy_var_1) ->
9591	case happyOut225 happy_x_2 of { (HappyWrap225 happy_var_2) ->
9592	happyIn224
9593		 (happy_var_2 : happy_var_1
9594	)}}
9595
9596happyReduce_572 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9597happyReduce_572 = happySpecReduce_0  208# happyReduction_572
9598happyReduction_572  =  happyIn224
9599		 ([]
9600	)
9601
9602happyReduce_573 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9603happyReduce_573 = happyMonadReduce 1# 209# happyReduction_573
9604happyReduction_573 (happy_x_1 `HappyStk`
9605	happyRest) tk
9606	 = happyThen ((case happyOut220 happy_x_1 of { (HappyWrap220 happy_var_1) ->
9607	( runECP_P happy_var_1 >>= \ cmd ->
9608                                    return (sL1 cmd $ HsCmdTop noExtField cmd))})
9609	) (\r -> happyReturn (happyIn225 r))
9610
9611happyReduce_574 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9612happyReduce_574 = happySpecReduce_3  210# happyReduction_574
9613happyReduction_574 happy_x_3
9614	happy_x_2
9615	happy_x_1
9616	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
9617	case happyOut227 happy_x_2 of { (HappyWrap227 happy_var_2) ->
9618	case happyOutTok happy_x_3 of { happy_var_3 ->
9619	happyIn226
9620		 (([mj AnnOpenC happy_var_1
9621                                                  ,mj AnnCloseC happy_var_3],happy_var_2)
9622	)}}}
9623
9624happyReduce_575 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9625happyReduce_575 = happySpecReduce_3  210# happyReduction_575
9626happyReduction_575 happy_x_3
9627	happy_x_2
9628	happy_x_1
9629	 =  case happyOut227 happy_x_2 of { (HappyWrap227 happy_var_2) ->
9630	happyIn226
9631		 (([],happy_var_2)
9632	)}
9633
9634happyReduce_576 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9635happyReduce_576 = happySpecReduce_1  211# happyReduction_576
9636happyReduction_576 happy_x_1
9637	 =  case happyOut76 happy_x_1 of { (HappyWrap76 happy_var_1) ->
9638	happyIn227
9639		 (cvTopDecls happy_var_1
9640	)}
9641
9642happyReduce_577 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9643happyReduce_577 = happySpecReduce_1  211# happyReduction_577
9644happyReduction_577 happy_x_1
9645	 =  case happyOut75 happy_x_1 of { (HappyWrap75 happy_var_1) ->
9646	happyIn227
9647		 (cvTopDecls happy_var_1
9648	)}
9649
9650happyReduce_578 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9651happyReduce_578 = happySpecReduce_1  212# happyReduction_578
9652happyReduction_578 happy_x_1
9653	 =  case happyOut209 happy_x_1 of { (HappyWrap209 happy_var_1) ->
9654	happyIn228
9655		 (happy_var_1
9656	)}
9657
9658happyReduce_579 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9659happyReduce_579 = happyMonadReduce 2# 212# happyReduction_579
9660happyReduction_579 (happy_x_2 `HappyStk`
9661	happy_x_1 `HappyStk`
9662	happyRest) tk
9663	 = happyThen ((case happyOut210 happy_x_1 of { (HappyWrap210 happy_var_1) ->
9664	case happyOut294 happy_x_2 of { (HappyWrap294 happy_var_2) ->
9665	( runECP_P happy_var_1 >>= \ happy_var_1 ->
9666                                runPV happy_var_2 >>= \ happy_var_2 ->
9667                                return $ ecpFromExp $
9668                                sLL happy_var_1 happy_var_2 $ SectionL noExtField happy_var_1 happy_var_2)}})
9669	) (\r -> happyReturn (happyIn228 r))
9670
9671happyReduce_580 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9672happyReduce_580 = happySpecReduce_2  212# happyReduction_580
9673happyReduction_580 happy_x_2
9674	happy_x_1
9675	 =  case happyOut295 happy_x_1 of { (HappyWrap295 happy_var_1) ->
9676	case happyOut210 happy_x_2 of { (HappyWrap210 happy_var_2) ->
9677	happyIn228
9678		 (ECP $
9679                                superInfixOp $
9680                                runECP_PV happy_var_2 >>= \ happy_var_2 ->
9681                                happy_var_1 >>= \ happy_var_1 ->
9682                                mkHsSectionR_PV (comb2 happy_var_1 happy_var_2) happy_var_1 happy_var_2
9683	)}}
9684
9685happyReduce_581 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9686happyReduce_581 = happySpecReduce_3  212# happyReduction_581
9687happyReduction_581 happy_x_3
9688	happy_x_2
9689	happy_x_1
9690	 =  case happyOut209 happy_x_1 of { (HappyWrap209 happy_var_1) ->
9691	case happyOutTok happy_x_2 of { happy_var_2 ->
9692	case happyOut228 happy_x_3 of { (HappyWrap228 happy_var_3) ->
9693	happyIn228
9694		 (ECP $
9695                             runECP_PV happy_var_1 >>= \ happy_var_1 ->
9696                             runECP_PV happy_var_3 >>= \ happy_var_3 ->
9697                             amms (mkHsViewPatPV (comb2 happy_var_1 happy_var_3) happy_var_1 happy_var_3) [mu AnnRarrow happy_var_2]
9698	)}}}
9699
9700happyReduce_582 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9701happyReduce_582 = happySpecReduce_2  213# happyReduction_582
9702happyReduction_582 happy_x_2
9703	happy_x_1
9704	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9705	case happyOut230 happy_x_2 of { (HappyWrap230 happy_var_2) ->
9706	happyIn229
9707		 (runECP_PV happy_var_1 >>= \ happy_var_1 ->
9708                             happy_var_2 >>= \ happy_var_2 ->
9709                             do { addAnnotation (gl happy_var_1) AnnComma (fst happy_var_2)
9710                                ; return ([],Tuple ((sL1 happy_var_1 (Just happy_var_1)) : snd happy_var_2)) }
9711	)}}
9712
9713happyReduce_583 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9714happyReduce_583 = happySpecReduce_2  213# happyReduction_583
9715happyReduction_583 happy_x_2
9716	happy_x_1
9717	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9718	case happyOut322 happy_x_2 of { (HappyWrap322 happy_var_2) ->
9719	happyIn229
9720		 (runECP_PV happy_var_1 >>= \ happy_var_1 -> return $
9721                            (mvbars (fst happy_var_2), Sum 1  (snd happy_var_2 + 1) happy_var_1)
9722	)}}
9723
9724happyReduce_584 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9725happyReduce_584 = happySpecReduce_2  213# happyReduction_584
9726happyReduction_584 happy_x_2
9727	happy_x_1
9728	 =  case happyOut320 happy_x_1 of { (HappyWrap320 happy_var_1) ->
9729	case happyOut231 happy_x_2 of { (HappyWrap231 happy_var_2) ->
9730	happyIn229
9731		 (happy_var_2 >>= \ happy_var_2 ->
9732                   do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (fst happy_var_1)
9733                      ; return
9734                           ([],Tuple (map (\l -> cL l Nothing) (fst happy_var_1) ++ happy_var_2)) }
9735	)}}
9736
9737happyReduce_585 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9738happyReduce_585 = happySpecReduce_3  213# happyReduction_585
9739happyReduction_585 happy_x_3
9740	happy_x_2
9741	happy_x_1
9742	 =  case happyOut322 happy_x_1 of { (HappyWrap322 happy_var_1) ->
9743	case happyOut228 happy_x_2 of { (HappyWrap228 happy_var_2) ->
9744	case happyOut321 happy_x_3 of { (HappyWrap321 happy_var_3) ->
9745	happyIn229
9746		 (runECP_PV happy_var_2 >>= \ happy_var_2 -> return $
9747                  (mvbars (fst happy_var_1) ++ mvbars (fst happy_var_3), Sum (snd happy_var_1 + 1) (snd happy_var_1 + snd happy_var_3 + 1) happy_var_2)
9748	)}}}
9749
9750happyReduce_586 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9751happyReduce_586 = happySpecReduce_2  214# happyReduction_586
9752happyReduction_586 happy_x_2
9753	happy_x_1
9754	 =  case happyOut320 happy_x_1 of { (HappyWrap320 happy_var_1) ->
9755	case happyOut231 happy_x_2 of { (HappyWrap231 happy_var_2) ->
9756	happyIn230
9757		 (happy_var_2 >>= \ happy_var_2 ->
9758          do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (tail $ fst happy_var_1)
9759             ; return (
9760            (head $ fst happy_var_1
9761            ,(map (\l -> cL l Nothing) (tail $ fst happy_var_1)) ++ happy_var_2)) }
9762	)}}
9763
9764happyReduce_587 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9765happyReduce_587 = happySpecReduce_2  215# happyReduction_587
9766happyReduction_587 happy_x_2
9767	happy_x_1
9768	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9769	case happyOut230 happy_x_2 of { (HappyWrap230 happy_var_2) ->
9770	happyIn231
9771		 (runECP_PV happy_var_1 >>= \ happy_var_1 ->
9772                                   happy_var_2 >>= \ happy_var_2 ->
9773                                   addAnnotation (gl happy_var_1) AnnComma (fst happy_var_2) >>
9774                                   return ((cL (gl happy_var_1) (Just happy_var_1)) : snd happy_var_2)
9775	)}}
9776
9777happyReduce_588 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9778happyReduce_588 = happySpecReduce_1  215# happyReduction_588
9779happyReduction_588 happy_x_1
9780	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9781	happyIn231
9782		 (runECP_PV happy_var_1 >>= \ happy_var_1 ->
9783                                   return [cL (gl happy_var_1) (Just happy_var_1)]
9784	)}
9785
9786happyReduce_589 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9787happyReduce_589 = happySpecReduce_0  215# happyReduction_589
9788happyReduction_589  =  happyIn231
9789		 (return [noLoc Nothing]
9790	)
9791
9792happyReduce_590 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9793happyReduce_590 = happySpecReduce_1  216# happyReduction_590
9794happyReduction_590 happy_x_1
9795	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9796	happyIn232
9797		 (\loc -> runECP_PV happy_var_1 >>= \ happy_var_1 ->
9798                            mkHsExplicitListPV loc [happy_var_1]
9799	)}
9800
9801happyReduce_591 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9802happyReduce_591 = happySpecReduce_1  216# happyReduction_591
9803happyReduction_591 happy_x_1
9804	 =  case happyOut233 happy_x_1 of { (HappyWrap233 happy_var_1) ->
9805	happyIn232
9806		 (\loc -> happy_var_1 >>= \ happy_var_1 ->
9807                            mkHsExplicitListPV loc (reverse happy_var_1)
9808	)}
9809
9810happyReduce_592 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9811happyReduce_592 = happySpecReduce_2  216# happyReduction_592
9812happyReduction_592 happy_x_2
9813	happy_x_1
9814	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9815	case happyOutTok happy_x_2 of { happy_var_2 ->
9816	happyIn232
9817		 (\loc ->    runECP_PV happy_var_1 >>= \ happy_var_1 ->
9818                                  ams (cL loc $ ArithSeq noExtField Nothing (From happy_var_1))
9819                                      [mj AnnDotdot happy_var_2]
9820                                      >>= ecpFromExp'
9821	)}}
9822
9823happyReduce_593 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9824happyReduce_593 = happyReduce 4# 216# happyReduction_593
9825happyReduction_593 (happy_x_4 `HappyStk`
9826	happy_x_3 `HappyStk`
9827	happy_x_2 `HappyStk`
9828	happy_x_1 `HappyStk`
9829	happyRest)
9830	 = case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9831	case happyOutTok happy_x_2 of { happy_var_2 ->
9832	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
9833	case happyOutTok happy_x_4 of { happy_var_4 ->
9834	happyIn232
9835		 (\loc ->
9836                                   runECP_PV happy_var_1 >>= \ happy_var_1 ->
9837                                   runECP_PV happy_var_3 >>= \ happy_var_3 ->
9838                                   ams (cL loc $ ArithSeq noExtField Nothing (FromThen happy_var_1 happy_var_3))
9839                                       [mj AnnComma happy_var_2,mj AnnDotdot happy_var_4]
9840                                       >>= ecpFromExp'
9841	) `HappyStk` happyRest}}}}
9842
9843happyReduce_594 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9844happyReduce_594 = happySpecReduce_3  216# happyReduction_594
9845happyReduction_594 happy_x_3
9846	happy_x_2
9847	happy_x_1
9848	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9849	case happyOutTok happy_x_2 of { happy_var_2 ->
9850	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
9851	happyIn232
9852		 (\loc -> runECP_PV happy_var_1 >>= \ happy_var_1 ->
9853                                   runECP_PV happy_var_3 >>= \ happy_var_3 ->
9854                                   ams (cL loc $ ArithSeq noExtField Nothing (FromTo happy_var_1 happy_var_3))
9855                                       [mj AnnDotdot happy_var_2]
9856                                       >>= ecpFromExp'
9857	)}}}
9858
9859happyReduce_595 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9860happyReduce_595 = happyReduce 5# 216# happyReduction_595
9861happyReduction_595 (happy_x_5 `HappyStk`
9862	happy_x_4 `HappyStk`
9863	happy_x_3 `HappyStk`
9864	happy_x_2 `HappyStk`
9865	happy_x_1 `HappyStk`
9866	happyRest)
9867	 = case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9868	case happyOutTok happy_x_2 of { happy_var_2 ->
9869	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
9870	case happyOutTok happy_x_4 of { happy_var_4 ->
9871	case happyOut209 happy_x_5 of { (HappyWrap209 happy_var_5) ->
9872	happyIn232
9873		 (\loc ->
9874                                   runECP_PV happy_var_1 >>= \ happy_var_1 ->
9875                                   runECP_PV happy_var_3 >>= \ happy_var_3 ->
9876                                   runECP_PV happy_var_5 >>= \ happy_var_5 ->
9877                                   ams (cL loc $ ArithSeq noExtField Nothing (FromThenTo happy_var_1 happy_var_3 happy_var_5))
9878                                       [mj AnnComma happy_var_2,mj AnnDotdot happy_var_4]
9879                                       >>= ecpFromExp'
9880	) `HappyStk` happyRest}}}}}
9881
9882happyReduce_596 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9883happyReduce_596 = happySpecReduce_3  216# happyReduction_596
9884happyReduction_596 happy_x_3
9885	happy_x_2
9886	happy_x_1
9887	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9888	case happyOutTok happy_x_2 of { happy_var_2 ->
9889	case happyOut234 happy_x_3 of { (HappyWrap234 happy_var_3) ->
9890	happyIn232
9891		 (\loc ->
9892                checkMonadComp >>= \ ctxt ->
9893                runECP_PV happy_var_1 >>= \ happy_var_1 ->
9894                ams (cL loc $ mkHsComp ctxt (unLoc happy_var_3) happy_var_1)
9895                    [mj AnnVbar happy_var_2]
9896                    >>= ecpFromExp'
9897	)}}}
9898
9899happyReduce_597 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9900happyReduce_597 = happySpecReduce_3  217# happyReduction_597
9901happyReduction_597 happy_x_3
9902	happy_x_2
9903	happy_x_1
9904	 =  case happyOut233 happy_x_1 of { (HappyWrap233 happy_var_1) ->
9905	case happyOutTok happy_x_2 of { happy_var_2 ->
9906	case happyOut228 happy_x_3 of { (HappyWrap228 happy_var_3) ->
9907	happyIn233
9908		 (happy_var_1 >>= \ happy_var_1 ->
9909                                     runECP_PV happy_var_3 >>= \ happy_var_3 ->
9910                                     addAnnotation (gl $ head $ happy_var_1)
9911                                                            AnnComma (gl happy_var_2) >>
9912                                      return (((:) $! happy_var_3) $! happy_var_1)
9913	)}}}
9914
9915happyReduce_598 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9916happyReduce_598 = happySpecReduce_3  217# happyReduction_598
9917happyReduction_598 happy_x_3
9918	happy_x_2
9919	happy_x_1
9920	 =  case happyOut228 happy_x_1 of { (HappyWrap228 happy_var_1) ->
9921	case happyOutTok happy_x_2 of { happy_var_2 ->
9922	case happyOut228 happy_x_3 of { (HappyWrap228 happy_var_3) ->
9923	happyIn233
9924		 (runECP_PV happy_var_1 >>= \ happy_var_1 ->
9925                                      runECP_PV happy_var_3 >>= \ happy_var_3 ->
9926                                      addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2) >>
9927                                      return [happy_var_3,happy_var_1]
9928	)}}}
9929
9930happyReduce_599 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9931happyReduce_599 = happySpecReduce_1  218# happyReduction_599
9932happyReduction_599 happy_x_1
9933	 =  case happyOut235 happy_x_1 of { (HappyWrap235 happy_var_1) ->
9934	happyIn234
9935		 (case (unLoc happy_var_1) of
9936                    [qs] -> sL1 happy_var_1 qs
9937                    -- We just had one thing in our "parallel" list so
9938                    -- we simply return that thing directly
9939
9940                    qss -> sL1 happy_var_1 [sL1 happy_var_1 $ ParStmt noExtField [ParStmtBlock noExtField qs [] noSyntaxExpr |
9941                                            qs <- qss]
9942                                            noExpr noSyntaxExpr]
9943                    -- We actually found some actual parallel lists so
9944                    -- we wrap them into as a ParStmt
9945	)}
9946
9947happyReduce_600 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9948happyReduce_600 = happyMonadReduce 3# 219# happyReduction_600
9949happyReduction_600 (happy_x_3 `HappyStk`
9950	happy_x_2 `HappyStk`
9951	happy_x_1 `HappyStk`
9952	happyRest) tk
9953	 = happyThen ((case happyOut236 happy_x_1 of { (HappyWrap236 happy_var_1) ->
9954	case happyOutTok happy_x_2 of { happy_var_2 ->
9955	case happyOut235 happy_x_3 of { (HappyWrap235 happy_var_3) ->
9956	( addAnnotation (gl $ head $ unLoc happy_var_1) AnnVbar (gl happy_var_2) >>
9957                        return (sLL happy_var_1 happy_var_3 (reverse (unLoc happy_var_1) : unLoc happy_var_3)))}}})
9958	) (\r -> happyReturn (happyIn235 r))
9959
9960happyReduce_601 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9961happyReduce_601 = happySpecReduce_1  219# happyReduction_601
9962happyReduction_601 happy_x_1
9963	 =  case happyOut236 happy_x_1 of { (HappyWrap236 happy_var_1) ->
9964	happyIn235
9965		 (cL (getLoc happy_var_1) [reverse (unLoc happy_var_1)]
9966	)}
9967
9968happyReduce_602 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9969happyReduce_602 = happyMonadReduce 3# 220# happyReduction_602
9970happyReduction_602 (happy_x_3 `HappyStk`
9971	happy_x_2 `HappyStk`
9972	happy_x_1 `HappyStk`
9973	happyRest) tk
9974	 = happyThen ((case happyOut236 happy_x_1 of { (HappyWrap236 happy_var_1) ->
9975	case happyOutTok happy_x_2 of { happy_var_2 ->
9976	case happyOut237 happy_x_3 of { (HappyWrap237 happy_var_3) ->
9977	( addAnnotation (gl $ head $ unLoc happy_var_1) AnnComma (gl happy_var_2) >>
9978                amsL (comb2 happy_var_1 happy_var_3) (fst $ unLoc happy_var_3) >>
9979                return (sLL happy_var_1 happy_var_3 [sLL happy_var_1 happy_var_3 ((snd $ unLoc happy_var_3) (reverse (unLoc happy_var_1)))]))}}})
9980	) (\r -> happyReturn (happyIn236 r))
9981
9982happyReduce_603 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9983happyReduce_603 = happyMonadReduce 3# 220# happyReduction_603
9984happyReduction_603 (happy_x_3 `HappyStk`
9985	happy_x_2 `HappyStk`
9986	happy_x_1 `HappyStk`
9987	happyRest) tk
9988	 = happyThen ((case happyOut236 happy_x_1 of { (HappyWrap236 happy_var_1) ->
9989	case happyOutTok happy_x_2 of { happy_var_2 ->
9990	case happyOut258 happy_x_3 of { (HappyWrap258 happy_var_3) ->
9991	( runPV happy_var_3 >>= \ happy_var_3 ->
9992                addAnnotation (gl $ head $ unLoc happy_var_1) AnnComma (gl happy_var_2) >>
9993                return (sLL happy_var_1 happy_var_3 (happy_var_3 : unLoc happy_var_1)))}}})
9994	) (\r -> happyReturn (happyIn236 r))
9995
9996happyReduce_604 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
9997happyReduce_604 = happyMonadReduce 1# 220# happyReduction_604
9998happyReduction_604 (happy_x_1 `HappyStk`
9999	happyRest) tk
10000	 = happyThen ((case happyOut237 happy_x_1 of { (HappyWrap237 happy_var_1) ->
10001	( ams happy_var_1 (fst $ unLoc happy_var_1) >>
10002                              return (sLL happy_var_1 happy_var_1 [cL (getLoc happy_var_1) ((snd $ unLoc happy_var_1) [])]))})
10003	) (\r -> happyReturn (happyIn236 r))
10004
10005happyReduce_605 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10006happyReduce_605 = happyMonadReduce 1# 220# happyReduction_605
10007happyReduction_605 (happy_x_1 `HappyStk`
10008	happyRest) tk
10009	 = happyThen ((case happyOut258 happy_x_1 of { (HappyWrap258 happy_var_1) ->
10010	( runPV happy_var_1 >>= \ happy_var_1 ->
10011                                            return $ sL1 happy_var_1 [happy_var_1])})
10012	) (\r -> happyReturn (happyIn236 r))
10013
10014happyReduce_606 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10015happyReduce_606 = happyMonadReduce 2# 221# happyReduction_606
10016happyReduction_606 (happy_x_2 `HappyStk`
10017	happy_x_1 `HappyStk`
10018	happyRest) tk
10019	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10020	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
10021	( runECP_P happy_var_2 >>= \ happy_var_2 -> return $
10022                                 sLL happy_var_1 happy_var_2 ([mj AnnThen happy_var_1], \ss -> (mkTransformStmt ss happy_var_2)))}})
10023	) (\r -> happyReturn (happyIn237 r))
10024
10025happyReduce_607 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10026happyReduce_607 = happyMonadReduce 4# 221# happyReduction_607
10027happyReduction_607 (happy_x_4 `HappyStk`
10028	happy_x_3 `HappyStk`
10029	happy_x_2 `HappyStk`
10030	happy_x_1 `HappyStk`
10031	happyRest) tk
10032	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10033	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
10034	case happyOutTok happy_x_3 of { happy_var_3 ->
10035	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
10036	( runECP_P happy_var_2 >>= \ happy_var_2 ->
10037                                 runECP_P happy_var_4 >>= \ happy_var_4 ->
10038                                 return $ sLL happy_var_1 happy_var_4 ([mj AnnThen happy_var_1,mj AnnBy  happy_var_3],
10039                                                     \ss -> (mkTransformByStmt ss happy_var_2 happy_var_4)))}}}})
10040	) (\r -> happyReturn (happyIn237 r))
10041
10042happyReduce_608 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10043happyReduce_608 = happyMonadReduce 4# 221# happyReduction_608
10044happyReduction_608 (happy_x_4 `HappyStk`
10045	happy_x_3 `HappyStk`
10046	happy_x_2 `HappyStk`
10047	happy_x_1 `HappyStk`
10048	happyRest) tk
10049	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10050	case happyOutTok happy_x_2 of { happy_var_2 ->
10051	case happyOutTok happy_x_3 of { happy_var_3 ->
10052	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
10053	( runECP_P happy_var_4 >>= \ happy_var_4 ->
10054               return $ sLL happy_var_1 happy_var_4 ([mj AnnThen happy_var_1,mj AnnGroup happy_var_2,mj AnnUsing happy_var_3],
10055                                   \ss -> (mkGroupUsingStmt ss happy_var_4)))}}}})
10056	) (\r -> happyReturn (happyIn237 r))
10057
10058happyReduce_609 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10059happyReduce_609 = happyMonadReduce 6# 221# happyReduction_609
10060happyReduction_609 (happy_x_6 `HappyStk`
10061	happy_x_5 `HappyStk`
10062	happy_x_4 `HappyStk`
10063	happy_x_3 `HappyStk`
10064	happy_x_2 `HappyStk`
10065	happy_x_1 `HappyStk`
10066	happyRest) tk
10067	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10068	case happyOutTok happy_x_2 of { happy_var_2 ->
10069	case happyOutTok happy_x_3 of { happy_var_3 ->
10070	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
10071	case happyOutTok happy_x_5 of { happy_var_5 ->
10072	case happyOut209 happy_x_6 of { (HappyWrap209 happy_var_6) ->
10073	( runECP_P happy_var_4 >>= \ happy_var_4 ->
10074               runECP_P happy_var_6 >>= \ happy_var_6 ->
10075               return $ sLL happy_var_1 happy_var_6 ([mj AnnThen happy_var_1,mj AnnGroup happy_var_2,mj AnnBy happy_var_3,mj AnnUsing happy_var_5],
10076                                   \ss -> (mkGroupByUsingStmt ss happy_var_4 happy_var_6)))}}}}}})
10077	) (\r -> happyReturn (happyIn237 r))
10078
10079happyReduce_610 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10080happyReduce_610 = happySpecReduce_1  222# happyReduction_610
10081happyReduction_610 happy_x_1
10082	 =  case happyOut239 happy_x_1 of { (HappyWrap239 happy_var_1) ->
10083	happyIn238
10084		 (cL (getLoc happy_var_1) (reverse (unLoc happy_var_1))
10085	)}
10086
10087happyReduce_611 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10088happyReduce_611 = happyMonadReduce 3# 223# happyReduction_611
10089happyReduction_611 (happy_x_3 `HappyStk`
10090	happy_x_2 `HappyStk`
10091	happy_x_1 `HappyStk`
10092	happyRest) tk
10093	 = happyThen ((case happyOut239 happy_x_1 of { (HappyWrap239 happy_var_1) ->
10094	case happyOutTok happy_x_2 of { happy_var_2 ->
10095	case happyOut258 happy_x_3 of { (HappyWrap258 happy_var_3) ->
10096	( runPV happy_var_3 >>= \ happy_var_3 ->
10097                               addAnnotation (gl $ head $ unLoc happy_var_1) AnnComma
10098                                             (gl happy_var_2) >>
10099                               return (sLL happy_var_1 happy_var_3 (happy_var_3 : unLoc happy_var_1)))}}})
10100	) (\r -> happyReturn (happyIn239 r))
10101
10102happyReduce_612 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10103happyReduce_612 = happyMonadReduce 1# 223# happyReduction_612
10104happyReduction_612 (happy_x_1 `HappyStk`
10105	happyRest) tk
10106	 = happyThen ((case happyOut258 happy_x_1 of { (HappyWrap258 happy_var_1) ->
10107	( runPV happy_var_1 >>= \ happy_var_1 ->
10108                               return $ sL1 happy_var_1 [happy_var_1])})
10109	) (\r -> happyReturn (happyIn239 r))
10110
10111happyReduce_613 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10112happyReduce_613 = happySpecReduce_3  224# happyReduction_613
10113happyReduction_613 happy_x_3
10114	happy_x_2
10115	happy_x_1
10116	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10117	case happyOut241 happy_x_2 of { (HappyWrap241 happy_var_2) ->
10118	case happyOutTok happy_x_3 of { happy_var_3 ->
10119	happyIn240
10120		 (happy_var_2 >>= \ happy_var_2 -> return $
10121                                     sLL happy_var_1 happy_var_3 ((moc happy_var_1:mcc happy_var_3:(fst $ unLoc happy_var_2))
10122                                               ,(reverse (snd $ unLoc happy_var_2)))
10123	)}}}
10124
10125happyReduce_614 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10126happyReduce_614 = happySpecReduce_3  224# happyReduction_614
10127happyReduction_614 happy_x_3
10128	happy_x_2
10129	happy_x_1
10130	 =  case happyOut241 happy_x_2 of { (HappyWrap241 happy_var_2) ->
10131	happyIn240
10132		 (happy_var_2 >>= \ happy_var_2 -> return $
10133                                       cL (getLoc happy_var_2) (fst $ unLoc happy_var_2
10134                                        ,(reverse (snd $ unLoc happy_var_2)))
10135	)}
10136
10137happyReduce_615 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10138happyReduce_615 = happySpecReduce_2  224# happyReduction_615
10139happyReduction_615 happy_x_2
10140	happy_x_1
10141	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10142	case happyOutTok happy_x_2 of { happy_var_2 ->
10143	happyIn240
10144		 (return $ sLL happy_var_1 happy_var_2 ([moc happy_var_1,mcc happy_var_2],[])
10145	)}}
10146
10147happyReduce_616 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10148happyReduce_616 = happySpecReduce_2  224# happyReduction_616
10149happyReduction_616 happy_x_2
10150	happy_x_1
10151	 =  happyIn240
10152		 (return $ noLoc ([],[])
10153	)
10154
10155happyReduce_617 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10156happyReduce_617 = happySpecReduce_1  225# happyReduction_617
10157happyReduction_617 happy_x_1
10158	 =  case happyOut242 happy_x_1 of { (HappyWrap242 happy_var_1) ->
10159	happyIn241
10160		 (happy_var_1 >>= \ happy_var_1 -> return $
10161                                     sL1 happy_var_1 (fst $ unLoc happy_var_1,snd $ unLoc happy_var_1)
10162	)}
10163
10164happyReduce_618 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10165happyReduce_618 = happySpecReduce_2  225# happyReduction_618
10166happyReduction_618 happy_x_2
10167	happy_x_1
10168	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10169	case happyOut241 happy_x_2 of { (HappyWrap241 happy_var_2) ->
10170	happyIn241
10171		 (happy_var_2 >>= \ happy_var_2 -> return $
10172                                     sLL happy_var_1 happy_var_2 ((mj AnnSemi happy_var_1:(fst $ unLoc happy_var_2))
10173                                               ,snd $ unLoc happy_var_2)
10174	)}}
10175
10176happyReduce_619 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10177happyReduce_619 = happySpecReduce_3  226# happyReduction_619
10178happyReduction_619 happy_x_3
10179	happy_x_2
10180	happy_x_1
10181	 =  case happyOut242 happy_x_1 of { (HappyWrap242 happy_var_1) ->
10182	case happyOutTok happy_x_2 of { happy_var_2 ->
10183	case happyOut243 happy_x_3 of { (HappyWrap243 happy_var_3) ->
10184	happyIn242
10185		 (happy_var_1 >>= \ happy_var_1 ->
10186                                  happy_var_3 >>= \ happy_var_3 ->
10187                                     if null (snd $ unLoc happy_var_1)
10188                                     then return (sLL happy_var_1 happy_var_3 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
10189                                                  ,[happy_var_3]))
10190                                     else (ams (head $ snd $ unLoc happy_var_1)
10191                                               (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1))
10192                                           >> return (sLL happy_var_1 happy_var_3 ([],happy_var_3 : (snd $ unLoc happy_var_1))) )
10193	)}}}
10194
10195happyReduce_620 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10196happyReduce_620 = happySpecReduce_2  226# happyReduction_620
10197happyReduction_620 happy_x_2
10198	happy_x_1
10199	 =  case happyOut242 happy_x_1 of { (HappyWrap242 happy_var_1) ->
10200	case happyOutTok happy_x_2 of { happy_var_2 ->
10201	happyIn242
10202		 (happy_var_1 >>= \ happy_var_1 ->
10203                                   if null (snd $ unLoc happy_var_1)
10204                                     then return (sLL happy_var_1 happy_var_2 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
10205                                                  ,snd $ unLoc happy_var_1))
10206                                     else (ams (head $ snd $ unLoc happy_var_1)
10207                                               (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1))
10208                                           >> return (sLL happy_var_1 happy_var_2 ([],snd $ unLoc happy_var_1)))
10209	)}}
10210
10211happyReduce_621 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10212happyReduce_621 = happySpecReduce_1  226# happyReduction_621
10213happyReduction_621 happy_x_1
10214	 =  case happyOut243 happy_x_1 of { (HappyWrap243 happy_var_1) ->
10215	happyIn242
10216		 (happy_var_1 >>= \ happy_var_1 -> return $ sL1 happy_var_1 ([],[happy_var_1])
10217	)}
10218
10219happyReduce_622 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10220happyReduce_622 = happySpecReduce_2  227# happyReduction_622
10221happyReduction_622 happy_x_2
10222	happy_x_1
10223	 =  case happyOut249 happy_x_1 of { (HappyWrap249 happy_var_1) ->
10224	case happyOut244 happy_x_2 of { (HappyWrap244 happy_var_2) ->
10225	happyIn243
10226		 (happy_var_2 >>= \ happy_var_2 ->
10227                            ams (sLL happy_var_1 happy_var_2 (Match { m_ext = noExtField
10228                                                  , m_ctxt = CaseAlt
10229                                                  , m_pats = [happy_var_1]
10230                                                  , m_grhss = snd $ unLoc happy_var_2 }))
10231                                      (fst $ unLoc happy_var_2)
10232	)}}
10233
10234happyReduce_623 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10235happyReduce_623 = happySpecReduce_2  228# happyReduction_623
10236happyReduction_623 happy_x_2
10237	happy_x_1
10238	 =  case happyOut245 happy_x_1 of { (HappyWrap245 happy_var_1) ->
10239	case happyOut128 happy_x_2 of { (HappyWrap128 happy_var_2) ->
10240	happyIn244
10241		 (happy_var_1 >>= \alt ->
10242                                      return $ sLL alt happy_var_2 (fst $ unLoc happy_var_2, GRHSs noExtField (unLoc alt) (snd $ unLoc happy_var_2))
10243	)}}
10244
10245happyReduce_624 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10246happyReduce_624 = happySpecReduce_2  229# happyReduction_624
10247happyReduction_624 happy_x_2
10248	happy_x_1
10249	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10250	case happyOut209 happy_x_2 of { (HappyWrap209 happy_var_2) ->
10251	happyIn245
10252		 (runECP_PV happy_var_2 >>= \ happy_var_2 ->
10253                                ams (sLL happy_var_1 happy_var_2 (unguardedRHS (comb2 happy_var_1 happy_var_2) happy_var_2))
10254                                    [mu AnnRarrow happy_var_1]
10255	)}}
10256
10257happyReduce_625 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10258happyReduce_625 = happySpecReduce_1  229# happyReduction_625
10259happyReduction_625 happy_x_1
10260	 =  case happyOut246 happy_x_1 of { (HappyWrap246 happy_var_1) ->
10261	happyIn245
10262		 (happy_var_1 >>= \gdpats ->
10263                                return $ sL1 gdpats (reverse (unLoc gdpats))
10264	)}
10265
10266happyReduce_626 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10267happyReduce_626 = happySpecReduce_2  230# happyReduction_626
10268happyReduction_626 happy_x_2
10269	happy_x_1
10270	 =  case happyOut246 happy_x_1 of { (HappyWrap246 happy_var_1) ->
10271	case happyOut248 happy_x_2 of { (HappyWrap248 happy_var_2) ->
10272	happyIn246
10273		 (happy_var_1 >>= \gdpats ->
10274                         happy_var_2 >>= \gdpat ->
10275                         return $ sLL gdpats gdpat (gdpat : unLoc gdpats)
10276	)}}
10277
10278happyReduce_627 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10279happyReduce_627 = happySpecReduce_1  230# happyReduction_627
10280happyReduction_627 happy_x_1
10281	 =  case happyOut248 happy_x_1 of { (HappyWrap248 happy_var_1) ->
10282	happyIn246
10283		 (happy_var_1 >>= \gdpat -> return $ sL1 gdpat [gdpat]
10284	)}
10285
10286happyReduce_628 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10287happyReduce_628 = happyMonadReduce 3# 231# happyReduction_628
10288happyReduction_628 (happy_x_3 `HappyStk`
10289	happy_x_2 `HappyStk`
10290	happy_x_1 `HappyStk`
10291	happyRest) tk
10292	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10293	case happyOut246 happy_x_2 of { (HappyWrap246 happy_var_2) ->
10294	case happyOutTok happy_x_3 of { happy_var_3 ->
10295	( runPV happy_var_2 >>= \ happy_var_2 ->
10296                                             return $ sLL happy_var_1 happy_var_3 ([moc happy_var_1,mcc happy_var_3],unLoc happy_var_2))}}})
10297	) (\r -> happyReturn (happyIn247 r))
10298
10299happyReduce_629 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10300happyReduce_629 = happyMonadReduce 2# 231# happyReduction_629
10301happyReduction_629 (happy_x_2 `HappyStk`
10302	happy_x_1 `HappyStk`
10303	happyRest) tk
10304	 = happyThen ((case happyOut246 happy_x_1 of { (HappyWrap246 happy_var_1) ->
10305	( runPV happy_var_1 >>= \ happy_var_1 ->
10306                                             return $ sL1 happy_var_1 ([],unLoc happy_var_1))})
10307	) (\r -> happyReturn (happyIn247 r))
10308
10309happyReduce_630 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10310happyReduce_630 = happyReduce 4# 232# happyReduction_630
10311happyReduction_630 (happy_x_4 `HappyStk`
10312	happy_x_3 `HappyStk`
10313	happy_x_2 `HappyStk`
10314	happy_x_1 `HappyStk`
10315	happyRest)
10316	 = case happyOutTok happy_x_1 of { happy_var_1 ->
10317	case happyOut238 happy_x_2 of { (HappyWrap238 happy_var_2) ->
10318	case happyOutTok happy_x_3 of { happy_var_3 ->
10319	case happyOut209 happy_x_4 of { (HappyWrap209 happy_var_4) ->
10320	happyIn248
10321		 (runECP_PV happy_var_4 >>= \ happy_var_4 ->
10322                                     ams (sL (comb2 happy_var_1 happy_var_4) $ GRHS noExtField (unLoc happy_var_2) happy_var_4)
10323                                         [mj AnnVbar happy_var_1,mu AnnRarrow happy_var_3]
10324	) `HappyStk` happyRest}}}}
10325
10326happyReduce_631 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10327happyReduce_631 = happyMonadReduce 1# 233# happyReduction_631
10328happyReduction_631 (happy_x_1 `HappyStk`
10329	happyRest) tk
10330	 = happyThen ((case happyOut209 happy_x_1 of { (HappyWrap209 happy_var_1) ->
10331	( (checkPattern <=< runECP_P) happy_var_1)})
10332	) (\r -> happyReturn (happyIn249 r))
10333
10334happyReduce_632 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10335happyReduce_632 = happyMonadReduce 2# 233# happyReduction_632
10336happyReduction_632 (happy_x_2 `HappyStk`
10337	happy_x_1 `HappyStk`
10338	happyRest) tk
10339	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10340	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
10341	( runECP_P happy_var_2 >>= \ happy_var_2 ->
10342                           amms (checkPattern (patBuilderBang (getLoc happy_var_1) happy_var_2))
10343                                [mj AnnBang happy_var_1])}})
10344	) (\r -> happyReturn (happyIn249 r))
10345
10346happyReduce_633 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10347happyReduce_633 = happyMonadReduce 1# 234# happyReduction_633
10348happyReduction_633 (happy_x_1 `HappyStk`
10349	happyRest) tk
10350	 = happyThen ((case happyOut209 happy_x_1 of { (HappyWrap209 happy_var_1) ->
10351	( -- See Note [Parser-Validator ReaderT SDoc] in RdrHsSyn
10352                             checkPattern_msg (text "Possibly caused by a missing 'do'?")
10353                                              (runECP_PV happy_var_1))})
10354	) (\r -> happyReturn (happyIn250 r))
10355
10356happyReduce_634 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10357happyReduce_634 = happyMonadReduce 2# 234# happyReduction_634
10358happyReduction_634 (happy_x_2 `HappyStk`
10359	happy_x_1 `HappyStk`
10360	happyRest) tk
10361	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10362	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
10363	( -- See Note [Parser-Validator ReaderT SDoc] in RdrHsSyn
10364                             amms (checkPattern_msg (text "Possibly caused by a missing 'do'?")
10365                                     (patBuilderBang (getLoc happy_var_1) `fmap` runECP_PV happy_var_2))
10366                                  [mj AnnBang happy_var_1])}})
10367	) (\r -> happyReturn (happyIn250 r))
10368
10369happyReduce_635 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10370happyReduce_635 = happyMonadReduce 1# 235# happyReduction_635
10371happyReduction_635 (happy_x_1 `HappyStk`
10372	happyRest) tk
10373	 = happyThen ((case happyOut218 happy_x_1 of { (HappyWrap218 happy_var_1) ->
10374	( (checkPattern <=< runECP_P) happy_var_1)})
10375	) (\r -> happyReturn (happyIn251 r))
10376
10377happyReduce_636 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10378happyReduce_636 = happyMonadReduce 2# 235# happyReduction_636
10379happyReduction_636 (happy_x_2 `HappyStk`
10380	happy_x_1 `HappyStk`
10381	happyRest) tk
10382	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10383	case happyOut218 happy_x_2 of { (HappyWrap218 happy_var_2) ->
10384	( runECP_P happy_var_2 >>= \ happy_var_2 ->
10385                                   amms (checkPattern (patBuilderBang (getLoc happy_var_1) happy_var_2))
10386                                        [mj AnnBang happy_var_1])}})
10387	) (\r -> happyReturn (happyIn251 r))
10388
10389happyReduce_637 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10390happyReduce_637 = happySpecReduce_2  236# happyReduction_637
10391happyReduction_637 happy_x_2
10392	happy_x_1
10393	 =  case happyOut251 happy_x_1 of { (HappyWrap251 happy_var_1) ->
10394	case happyOut252 happy_x_2 of { (HappyWrap252 happy_var_2) ->
10395	happyIn252
10396		 (happy_var_1 : happy_var_2
10397	)}}
10398
10399happyReduce_638 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10400happyReduce_638 = happySpecReduce_0  236# happyReduction_638
10401happyReduction_638  =  happyIn252
10402		 ([]
10403	)
10404
10405happyReduce_639 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10406happyReduce_639 = happySpecReduce_3  237# happyReduction_639
10407happyReduction_639 happy_x_3
10408	happy_x_2
10409	happy_x_1
10410	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10411	case happyOut254 happy_x_2 of { (HappyWrap254 happy_var_2) ->
10412	case happyOutTok happy_x_3 of { happy_var_3 ->
10413	happyIn253
10414		 (happy_var_2 >>= \ happy_var_2 -> return $
10415                                          sLL happy_var_1 happy_var_3 ((moc happy_var_1:mcc happy_var_3:(fst $ unLoc happy_var_2))
10416                                             ,(reverse $ snd $ unLoc happy_var_2))
10417	)}}}
10418
10419happyReduce_640 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10420happyReduce_640 = happySpecReduce_3  237# happyReduction_640
10421happyReduction_640 happy_x_3
10422	happy_x_2
10423	happy_x_1
10424	 =  case happyOut254 happy_x_2 of { (HappyWrap254 happy_var_2) ->
10425	happyIn253
10426		 (happy_var_2 >>= \ happy_var_2 -> return $
10427                                          cL (gl happy_var_2) (fst $ unLoc happy_var_2
10428                                                    ,reverse $ snd $ unLoc happy_var_2)
10429	)}
10430
10431happyReduce_641 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10432happyReduce_641 = happySpecReduce_3  238# happyReduction_641
10433happyReduction_641 happy_x_3
10434	happy_x_2
10435	happy_x_1
10436	 =  case happyOut254 happy_x_1 of { (HappyWrap254 happy_var_1) ->
10437	case happyOutTok happy_x_2 of { happy_var_2 ->
10438	case happyOut257 happy_x_3 of { (HappyWrap257 happy_var_3) ->
10439	happyIn254
10440		 (happy_var_1 >>= \ happy_var_1 ->
10441                            happy_var_3 >>= \ happy_var_3 ->
10442                            if null (snd $ unLoc happy_var_1)
10443                              then return (sLL happy_var_1 happy_var_3 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1)
10444                                                     ,happy_var_3 : (snd $ unLoc happy_var_1)))
10445                              else do
10446                               { ams (head $ snd $ unLoc happy_var_1) [mj AnnSemi happy_var_2]
10447                               ; return $ sLL happy_var_1 happy_var_3 (fst $ unLoc happy_var_1,happy_var_3 :(snd $ unLoc happy_var_1)) }
10448	)}}}
10449
10450happyReduce_642 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10451happyReduce_642 = happySpecReduce_2  238# happyReduction_642
10452happyReduction_642 happy_x_2
10453	happy_x_1
10454	 =  case happyOut254 happy_x_1 of { (HappyWrap254 happy_var_1) ->
10455	case happyOutTok happy_x_2 of { happy_var_2 ->
10456	happyIn254
10457		 (happy_var_1 >>= \ happy_var_1 ->
10458                           if null (snd $ unLoc happy_var_1)
10459                             then return (sLL happy_var_1 happy_var_2 (mj AnnSemi happy_var_2:(fst $ unLoc happy_var_1),snd $ unLoc happy_var_1))
10460                             else do
10461                               { ams (head $ snd $ unLoc happy_var_1)
10462                                               [mj AnnSemi happy_var_2]
10463                               ; return happy_var_1 }
10464	)}}
10465
10466happyReduce_643 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10467happyReduce_643 = happySpecReduce_1  238# happyReduction_643
10468happyReduction_643 happy_x_1
10469	 =  case happyOut257 happy_x_1 of { (HappyWrap257 happy_var_1) ->
10470	happyIn254
10471		 (happy_var_1 >>= \ happy_var_1 ->
10472                                   return $ sL1 happy_var_1 ([],[happy_var_1])
10473	)}
10474
10475happyReduce_644 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10476happyReduce_644 = happySpecReduce_0  238# happyReduction_644
10477happyReduction_644  =  happyIn254
10478		 (return $ noLoc ([],[])
10479	)
10480
10481happyReduce_645 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10482happyReduce_645 = happyMonadReduce 1# 239# happyReduction_645
10483happyReduction_645 (happy_x_1 `HappyStk`
10484	happyRest) tk
10485	 = happyThen ((case happyOut257 happy_x_1 of { (HappyWrap257 happy_var_1) ->
10486	( fmap Just (runPV happy_var_1))})
10487	) (\r -> happyReturn (happyIn255 r))
10488
10489happyReduce_646 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10490happyReduce_646 = happySpecReduce_0  239# happyReduction_646
10491happyReduction_646  =  happyIn255
10492		 (Nothing
10493	)
10494
10495happyReduce_647 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10496happyReduce_647 = happyMonadReduce 1# 240# happyReduction_647
10497happyReduction_647 (happy_x_1 `HappyStk`
10498	happyRest) tk
10499	 = happyThen ((case happyOut257 happy_x_1 of { (HappyWrap257 happy_var_1) ->
10500	( runPV happy_var_1)})
10501	) (\r -> happyReturn (happyIn256 r))
10502
10503happyReduce_648 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10504happyReduce_648 = happySpecReduce_1  241# happyReduction_648
10505happyReduction_648 happy_x_1
10506	 =  case happyOut258 happy_x_1 of { (HappyWrap258 happy_var_1) ->
10507	happyIn257
10508		 (happy_var_1
10509	)}
10510
10511happyReduce_649 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10512happyReduce_649 = happySpecReduce_2  241# happyReduction_649
10513happyReduction_649 happy_x_2
10514	happy_x_1
10515	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10516	case happyOut253 happy_x_2 of { (HappyWrap253 happy_var_2) ->
10517	happyIn257
10518		 (happy_var_2 >>= \ happy_var_2 ->
10519                                           ams (sLL happy_var_1 happy_var_2 $ mkRecStmt (snd $ unLoc happy_var_2))
10520                                               (mj AnnRec happy_var_1:(fst $ unLoc happy_var_2))
10521	)}}
10522
10523happyReduce_650 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10524happyReduce_650 = happySpecReduce_3  242# happyReduction_650
10525happyReduction_650 happy_x_3
10526	happy_x_2
10527	happy_x_1
10528	 =  case happyOut250 happy_x_1 of { (HappyWrap250 happy_var_1) ->
10529	case happyOutTok happy_x_2 of { happy_var_2 ->
10530	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
10531	happyIn258
10532		 (runECP_PV happy_var_3 >>= \ happy_var_3 ->
10533                                           ams (sLL happy_var_1 happy_var_3 $ mkBindStmt happy_var_1 happy_var_3)
10534                                               [mu AnnLarrow happy_var_2]
10535	)}}}
10536
10537happyReduce_651 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10538happyReduce_651 = happySpecReduce_1  242# happyReduction_651
10539happyReduction_651 happy_x_1
10540	 =  case happyOut209 happy_x_1 of { (HappyWrap209 happy_var_1) ->
10541	happyIn258
10542		 (runECP_PV happy_var_1 >>= \ happy_var_1 ->
10543                                           return $ sL1 happy_var_1 $ mkBodyStmt happy_var_1
10544	)}
10545
10546happyReduce_652 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10547happyReduce_652 = happySpecReduce_2  242# happyReduction_652
10548happyReduction_652 happy_x_2
10549	happy_x_1
10550	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10551	case happyOut127 happy_x_2 of { (HappyWrap127 happy_var_2) ->
10552	happyIn258
10553		 (ams (sLL happy_var_1 happy_var_2 $ LetStmt noExtField (snd $ unLoc happy_var_2))
10554                                               (mj AnnLet happy_var_1:(fst $ unLoc happy_var_2))
10555	)}}
10556
10557happyReduce_653 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10558happyReduce_653 = happySpecReduce_1  243# happyReduction_653
10559happyReduction_653 happy_x_1
10560	 =  case happyOut260 happy_x_1 of { (HappyWrap260 happy_var_1) ->
10561	happyIn259
10562		 (happy_var_1
10563	)}
10564
10565happyReduce_654 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10566happyReduce_654 = happySpecReduce_0  243# happyReduction_654
10567happyReduction_654  =  happyIn259
10568		 (return ([],([], Nothing))
10569	)
10570
10571happyReduce_655 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10572happyReduce_655 = happySpecReduce_3  244# happyReduction_655
10573happyReduction_655 happy_x_3
10574	happy_x_2
10575	happy_x_1
10576	 =  case happyOut261 happy_x_1 of { (HappyWrap261 happy_var_1) ->
10577	case happyOutTok happy_x_2 of { happy_var_2 ->
10578	case happyOut260 happy_x_3 of { (HappyWrap260 happy_var_3) ->
10579	happyIn260
10580		 (happy_var_1 >>= \ happy_var_1 ->
10581                   happy_var_3 >>= \ happy_var_3 ->
10582                   addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2) >>
10583                   return (case happy_var_3 of (ma,(flds, dd)) -> (ma,(happy_var_1 : flds, dd)))
10584	)}}}
10585
10586happyReduce_656 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10587happyReduce_656 = happySpecReduce_1  244# happyReduction_656
10588happyReduction_656 happy_x_1
10589	 =  case happyOut261 happy_x_1 of { (HappyWrap261 happy_var_1) ->
10590	happyIn260
10591		 (happy_var_1 >>= \ happy_var_1 ->
10592                                          return ([],([happy_var_1], Nothing))
10593	)}
10594
10595happyReduce_657 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10596happyReduce_657 = happySpecReduce_1  244# happyReduction_657
10597happyReduction_657 happy_x_1
10598	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10599	happyIn260
10600		 (return ([mj AnnDotdot happy_var_1],([],   Just (getLoc happy_var_1)))
10601	)}
10602
10603happyReduce_658 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10604happyReduce_658 = happySpecReduce_3  245# happyReduction_658
10605happyReduction_658 happy_x_3
10606	happy_x_2
10607	happy_x_1
10608	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
10609	case happyOutTok happy_x_2 of { happy_var_2 ->
10610	case happyOut228 happy_x_3 of { (HappyWrap228 happy_var_3) ->
10611	happyIn261
10612		 (runECP_PV happy_var_3 >>= \ happy_var_3 ->
10613                           ams  (sLL happy_var_1 happy_var_3 $ HsRecField (sL1 happy_var_1 $ mkFieldOcc happy_var_1) happy_var_3 False)
10614                                [mj AnnEqual happy_var_2]
10615	)}}}
10616
10617happyReduce_659 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10618happyReduce_659 = happySpecReduce_1  245# happyReduction_659
10619happyReduction_659 happy_x_1
10620	 =  case happyOut303 happy_x_1 of { (HappyWrap303 happy_var_1) ->
10621	happyIn261
10622		 (placeHolderPunRhs >>= \rhs ->
10623                          return $ sLL happy_var_1 happy_var_1 $ HsRecField (sL1 happy_var_1 $ mkFieldOcc happy_var_1) rhs True
10624	)}
10625
10626happyReduce_660 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10627happyReduce_660 = happyMonadReduce 3# 246# happyReduction_660
10628happyReduction_660 (happy_x_3 `HappyStk`
10629	happy_x_2 `HappyStk`
10630	happy_x_1 `HappyStk`
10631	happyRest) tk
10632	 = happyThen ((case happyOut262 happy_x_1 of { (HappyWrap262 happy_var_1) ->
10633	case happyOutTok happy_x_2 of { happy_var_2 ->
10634	case happyOut263 happy_x_3 of { (HappyWrap263 happy_var_3) ->
10635	( addAnnotation (gl $ last $ unLoc happy_var_1) AnnSemi (gl happy_var_2) >>
10636                         return (let { this = happy_var_3; rest = unLoc happy_var_1 }
10637                              in rest `seq` this `seq` sLL happy_var_1 happy_var_3 (this : rest)))}}})
10638	) (\r -> happyReturn (happyIn262 r))
10639
10640happyReduce_661 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10641happyReduce_661 = happyMonadReduce 2# 246# happyReduction_661
10642happyReduction_661 (happy_x_2 `HappyStk`
10643	happy_x_1 `HappyStk`
10644	happyRest) tk
10645	 = happyThen ((case happyOut262 happy_x_1 of { (HappyWrap262 happy_var_1) ->
10646	case happyOutTok happy_x_2 of { happy_var_2 ->
10647	( addAnnotation (gl $ last $ unLoc happy_var_1) AnnSemi (gl happy_var_2) >>
10648                         return (sLL happy_var_1 happy_var_2 (unLoc happy_var_1)))}})
10649	) (\r -> happyReturn (happyIn262 r))
10650
10651happyReduce_662 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10652happyReduce_662 = happySpecReduce_1  246# happyReduction_662
10653happyReduction_662 happy_x_1
10654	 =  case happyOut263 happy_x_1 of { (HappyWrap263 happy_var_1) ->
10655	happyIn262
10656		 (let this = happy_var_1 in this `seq` sL1 happy_var_1 [this]
10657	)}
10658
10659happyReduce_663 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10660happyReduce_663 = happyMonadReduce 3# 247# happyReduction_663
10661happyReduction_663 (happy_x_3 `HappyStk`
10662	happy_x_2 `HappyStk`
10663	happy_x_1 `HappyStk`
10664	happyRest) tk
10665	 = happyThen ((case happyOut264 happy_x_1 of { (HappyWrap264 happy_var_1) ->
10666	case happyOutTok happy_x_2 of { happy_var_2 ->
10667	case happyOut209 happy_x_3 of { (HappyWrap209 happy_var_3) ->
10668	( runECP_P happy_var_3 >>= \ happy_var_3 ->
10669                                          ams (sLL happy_var_1 happy_var_3 (IPBind noExtField (Left happy_var_1) happy_var_3))
10670                                              [mj AnnEqual happy_var_2])}}})
10671	) (\r -> happyReturn (happyIn263 r))
10672
10673happyReduce_664 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10674happyReduce_664 = happySpecReduce_1  248# happyReduction_664
10675happyReduction_664 happy_x_1
10676	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10677	happyIn264
10678		 (sL1 happy_var_1 (HsIPName (getIPDUPVARID happy_var_1))
10679	)}
10680
10681happyReduce_665 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10682happyReduce_665 = happySpecReduce_1  249# happyReduction_665
10683happyReduction_665 happy_x_1
10684	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
10685	happyIn265
10686		 (sL1 happy_var_1 (getLABELVARID happy_var_1)
10687	)}
10688
10689happyReduce_666 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10690happyReduce_666 = happySpecReduce_1  250# happyReduction_666
10691happyReduction_666 happy_x_1
10692	 =  case happyOut267 happy_x_1 of { (HappyWrap267 happy_var_1) ->
10693	happyIn266
10694		 (happy_var_1
10695	)}
10696
10697happyReduce_667 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10698happyReduce_667 = happySpecReduce_0  250# happyReduction_667
10699happyReduction_667  =  happyIn266
10700		 (noLoc mkTrue
10701	)
10702
10703happyReduce_668 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10704happyReduce_668 = happySpecReduce_1  251# happyReduction_668
10705happyReduction_668 happy_x_1
10706	 =  case happyOut268 happy_x_1 of { (HappyWrap268 happy_var_1) ->
10707	happyIn267
10708		 (happy_var_1
10709	)}
10710
10711happyReduce_669 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10712happyReduce_669 = happyMonadReduce 3# 251# happyReduction_669
10713happyReduction_669 (happy_x_3 `HappyStk`
10714	happy_x_2 `HappyStk`
10715	happy_x_1 `HappyStk`
10716	happyRest) tk
10717	 = happyThen ((case happyOut268 happy_x_1 of { (HappyWrap268 happy_var_1) ->
10718	case happyOutTok happy_x_2 of { happy_var_2 ->
10719	case happyOut267 happy_x_3 of { (HappyWrap267 happy_var_3) ->
10720	( aa happy_var_1 (AnnVbar, happy_var_2)
10721                              >> return (sLL happy_var_1 happy_var_3 (Or [happy_var_1,happy_var_3])))}}})
10722	) (\r -> happyReturn (happyIn267 r))
10723
10724happyReduce_670 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10725happyReduce_670 = happySpecReduce_1  252# happyReduction_670
10726happyReduction_670 happy_x_1
10727	 =  case happyOut269 happy_x_1 of { (HappyWrap269 happy_var_1) ->
10728	happyIn268
10729		 (sLL (head happy_var_1) (last happy_var_1) (And (happy_var_1))
10730	)}
10731
10732happyReduce_671 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10733happyReduce_671 = happySpecReduce_1  253# happyReduction_671
10734happyReduction_671 happy_x_1
10735	 =  case happyOut270 happy_x_1 of { (HappyWrap270 happy_var_1) ->
10736	happyIn269
10737		 ([happy_var_1]
10738	)}
10739
10740happyReduce_672 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10741happyReduce_672 = happyMonadReduce 3# 253# happyReduction_672
10742happyReduction_672 (happy_x_3 `HappyStk`
10743	happy_x_2 `HappyStk`
10744	happy_x_1 `HappyStk`
10745	happyRest) tk
10746	 = happyThen ((case happyOut270 happy_x_1 of { (HappyWrap270 happy_var_1) ->
10747	case happyOutTok happy_x_2 of { happy_var_2 ->
10748	case happyOut269 happy_x_3 of { (HappyWrap269 happy_var_3) ->
10749	( aa happy_var_1 (AnnComma, happy_var_2) >> return (happy_var_1 : happy_var_3))}}})
10750	) (\r -> happyReturn (happyIn269 r))
10751
10752happyReduce_673 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10753happyReduce_673 = happyMonadReduce 3# 254# happyReduction_673
10754happyReduction_673 (happy_x_3 `HappyStk`
10755	happy_x_2 `HappyStk`
10756	happy_x_1 `HappyStk`
10757	happyRest) tk
10758	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10759	case happyOut267 happy_x_2 of { (HappyWrap267 happy_var_2) ->
10760	case happyOutTok happy_x_3 of { happy_var_3 ->
10761	( ams (sLL happy_var_1 happy_var_3 (Parens happy_var_2)) [mop happy_var_1,mcp happy_var_3])}}})
10762	) (\r -> happyReturn (happyIn270 r))
10763
10764happyReduce_674 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10765happyReduce_674 = happySpecReduce_1  254# happyReduction_674
10766happyReduction_674 happy_x_1
10767	 =  case happyOut272 happy_x_1 of { (HappyWrap272 happy_var_1) ->
10768	happyIn270
10769		 (sL1 happy_var_1 (Var happy_var_1)
10770	)}
10771
10772happyReduce_675 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10773happyReduce_675 = happySpecReduce_1  255# happyReduction_675
10774happyReduction_675 happy_x_1
10775	 =  case happyOut272 happy_x_1 of { (HappyWrap272 happy_var_1) ->
10776	happyIn271
10777		 (sL1 happy_var_1 [happy_var_1]
10778	)}
10779
10780happyReduce_676 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10781happyReduce_676 = happyMonadReduce 3# 255# happyReduction_676
10782happyReduction_676 (happy_x_3 `HappyStk`
10783	happy_x_2 `HappyStk`
10784	happy_x_1 `HappyStk`
10785	happyRest) tk
10786	 = happyThen ((case happyOut272 happy_x_1 of { (HappyWrap272 happy_var_1) ->
10787	case happyOutTok happy_x_2 of { happy_var_2 ->
10788	case happyOut271 happy_x_3 of { (HappyWrap271 happy_var_3) ->
10789	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2) >>
10790                                    return (sLL happy_var_1 happy_var_3 (happy_var_1 : unLoc happy_var_3)))}}})
10791	) (\r -> happyReturn (happyIn271 r))
10792
10793happyReduce_677 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10794happyReduce_677 = happySpecReduce_1  256# happyReduction_677
10795happyReduction_677 happy_x_1
10796	 =  case happyOut302 happy_x_1 of { (HappyWrap302 happy_var_1) ->
10797	happyIn272
10798		 (happy_var_1
10799	)}
10800
10801happyReduce_678 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10802happyReduce_678 = happySpecReduce_1  256# happyReduction_678
10803happyReduction_678 happy_x_1
10804	 =  case happyOut276 happy_x_1 of { (HappyWrap276 happy_var_1) ->
10805	happyIn272
10806		 (happy_var_1
10807	)}
10808
10809happyReduce_679 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10810happyReduce_679 = happySpecReduce_1  257# happyReduction_679
10811happyReduction_679 happy_x_1
10812	 =  case happyOut275 happy_x_1 of { (HappyWrap275 happy_var_1) ->
10813	happyIn273
10814		 (happy_var_1
10815	)}
10816
10817happyReduce_680 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10818happyReduce_680 = happySpecReduce_1  257# happyReduction_680
10819happyReduction_680 happy_x_1
10820	 =  case happyOut278 happy_x_1 of { (HappyWrap278 happy_var_1) ->
10821	happyIn273
10822		 (sL1 happy_var_1 $ nameRdrName (dataConName (unLoc happy_var_1))
10823	)}
10824
10825happyReduce_681 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10826happyReduce_681 = happySpecReduce_1  258# happyReduction_681
10827happyReduction_681 happy_x_1
10828	 =  case happyOut275 happy_x_1 of { (HappyWrap275 happy_var_1) ->
10829	happyIn274
10830		 (happy_var_1
10831	)}
10832
10833happyReduce_682 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10834happyReduce_682 = happySpecReduce_1  258# happyReduction_682
10835happyReduction_682 happy_x_1
10836	 =  case happyOut279 happy_x_1 of { (HappyWrap279 happy_var_1) ->
10837	happyIn274
10838		 (sL1 happy_var_1 $ nameRdrName (dataConName (unLoc happy_var_1))
10839	)}
10840
10841happyReduce_683 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10842happyReduce_683 = happySpecReduce_1  259# happyReduction_683
10843happyReduction_683 happy_x_1
10844	 =  case happyOut313 happy_x_1 of { (HappyWrap313 happy_var_1) ->
10845	happyIn275
10846		 (happy_var_1
10847	)}
10848
10849happyReduce_684 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10850happyReduce_684 = happyMonadReduce 3# 259# happyReduction_684
10851happyReduction_684 (happy_x_3 `HappyStk`
10852	happy_x_2 `HappyStk`
10853	happy_x_1 `HappyStk`
10854	happyRest) tk
10855	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10856	case happyOut315 happy_x_2 of { (HappyWrap315 happy_var_2) ->
10857	case happyOutTok happy_x_3 of { happy_var_3 ->
10858	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
10859                                   [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
10860	) (\r -> happyReturn (happyIn275 r))
10861
10862happyReduce_685 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10863happyReduce_685 = happySpecReduce_1  260# happyReduction_685
10864happyReduction_685 happy_x_1
10865	 =  case happyOut314 happy_x_1 of { (HappyWrap314 happy_var_1) ->
10866	happyIn276
10867		 (happy_var_1
10868	)}
10869
10870happyReduce_686 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10871happyReduce_686 = happyMonadReduce 3# 260# happyReduction_686
10872happyReduction_686 (happy_x_3 `HappyStk`
10873	happy_x_2 `HappyStk`
10874	happy_x_1 `HappyStk`
10875	happyRest) tk
10876	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10877	case happyOut316 happy_x_2 of { (HappyWrap316 happy_var_2) ->
10878	case happyOutTok happy_x_3 of { happy_var_3 ->
10879	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
10880                                       [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
10881	) (\r -> happyReturn (happyIn276 r))
10882
10883happyReduce_687 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10884happyReduce_687 = happySpecReduce_1  260# happyReduction_687
10885happyReduction_687 happy_x_1
10886	 =  case happyOut279 happy_x_1 of { (HappyWrap279 happy_var_1) ->
10887	happyIn276
10888		 (sL1 happy_var_1 $ nameRdrName (dataConName (unLoc happy_var_1))
10889	)}
10890
10891happyReduce_688 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10892happyReduce_688 = happySpecReduce_1  261# happyReduction_688
10893happyReduction_688 happy_x_1
10894	 =  case happyOut276 happy_x_1 of { (HappyWrap276 happy_var_1) ->
10895	happyIn277
10896		 (sL1 happy_var_1 [happy_var_1]
10897	)}
10898
10899happyReduce_689 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10900happyReduce_689 = happyMonadReduce 3# 261# happyReduction_689
10901happyReduction_689 (happy_x_3 `HappyStk`
10902	happy_x_2 `HappyStk`
10903	happy_x_1 `HappyStk`
10904	happyRest) tk
10905	 = happyThen ((case happyOut276 happy_x_1 of { (HappyWrap276 happy_var_1) ->
10906	case happyOutTok happy_x_2 of { happy_var_2 ->
10907	case happyOut277 happy_x_3 of { (HappyWrap277 happy_var_3) ->
10908	( addAnnotation (gl happy_var_1) AnnComma (gl happy_var_2) >>
10909                                   return (sLL happy_var_1 happy_var_3 (happy_var_1 : unLoc happy_var_3)))}}})
10910	) (\r -> happyReturn (happyIn277 r))
10911
10912happyReduce_690 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10913happyReduce_690 = happyMonadReduce 2# 262# happyReduction_690
10914happyReduction_690 (happy_x_2 `HappyStk`
10915	happy_x_1 `HappyStk`
10916	happyRest) tk
10917	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10918	case happyOutTok happy_x_2 of { happy_var_2 ->
10919	( ams (sLL happy_var_1 happy_var_2 unitDataCon) [mop happy_var_1,mcp happy_var_2])}})
10920	) (\r -> happyReturn (happyIn278 r))
10921
10922happyReduce_691 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10923happyReduce_691 = happyMonadReduce 3# 262# happyReduction_691
10924happyReduction_691 (happy_x_3 `HappyStk`
10925	happy_x_2 `HappyStk`
10926	happy_x_1 `HappyStk`
10927	happyRest) tk
10928	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10929	case happyOut320 happy_x_2 of { (HappyWrap320 happy_var_2) ->
10930	case happyOutTok happy_x_3 of { happy_var_3 ->
10931	( ams (sLL happy_var_1 happy_var_3 $ tupleDataCon Boxed (snd happy_var_2 + 1))
10932                                       (mop happy_var_1:mcp happy_var_3:(mcommas (fst happy_var_2))))}}})
10933	) (\r -> happyReturn (happyIn278 r))
10934
10935happyReduce_692 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10936happyReduce_692 = happyMonadReduce 2# 262# happyReduction_692
10937happyReduction_692 (happy_x_2 `HappyStk`
10938	happy_x_1 `HappyStk`
10939	happyRest) tk
10940	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10941	case happyOutTok happy_x_2 of { happy_var_2 ->
10942	( ams (sLL happy_var_1 happy_var_2 $ unboxedUnitDataCon) [mo happy_var_1,mc happy_var_2])}})
10943	) (\r -> happyReturn (happyIn278 r))
10944
10945happyReduce_693 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10946happyReduce_693 = happyMonadReduce 3# 262# happyReduction_693
10947happyReduction_693 (happy_x_3 `HappyStk`
10948	happy_x_2 `HappyStk`
10949	happy_x_1 `HappyStk`
10950	happyRest) tk
10951	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10952	case happyOut320 happy_x_2 of { (HappyWrap320 happy_var_2) ->
10953	case happyOutTok happy_x_3 of { happy_var_3 ->
10954	( ams (sLL happy_var_1 happy_var_3 $ tupleDataCon Unboxed (snd happy_var_2 + 1))
10955                                       (mo happy_var_1:mc happy_var_3:(mcommas (fst happy_var_2))))}}})
10956	) (\r -> happyReturn (happyIn278 r))
10957
10958happyReduce_694 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10959happyReduce_694 = happySpecReduce_1  263# happyReduction_694
10960happyReduction_694 happy_x_1
10961	 =  case happyOut278 happy_x_1 of { (HappyWrap278 happy_var_1) ->
10962	happyIn279
10963		 (happy_var_1
10964	)}
10965
10966happyReduce_695 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10967happyReduce_695 = happyMonadReduce 2# 263# happyReduction_695
10968happyReduction_695 (happy_x_2 `HappyStk`
10969	happy_x_1 `HappyStk`
10970	happyRest) tk
10971	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10972	case happyOutTok happy_x_2 of { happy_var_2 ->
10973	( ams (sLL happy_var_1 happy_var_2 nilDataCon) [mos happy_var_1,mcs happy_var_2])}})
10974	) (\r -> happyReturn (happyIn279 r))
10975
10976happyReduce_696 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10977happyReduce_696 = happySpecReduce_1  264# happyReduction_696
10978happyReduction_696 happy_x_1
10979	 =  case happyOut316 happy_x_1 of { (HappyWrap316 happy_var_1) ->
10980	happyIn280
10981		 (happy_var_1
10982	)}
10983
10984happyReduce_697 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10985happyReduce_697 = happyMonadReduce 3# 264# happyReduction_697
10986happyReduction_697 (happy_x_3 `HappyStk`
10987	happy_x_2 `HappyStk`
10988	happy_x_1 `HappyStk`
10989	happyRest) tk
10990	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
10991	case happyOut314 happy_x_2 of { (HappyWrap314 happy_var_2) ->
10992	case happyOutTok happy_x_3 of { happy_var_3 ->
10993	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
10994                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
10995                                       ,mj AnnBackquote happy_var_3])}}})
10996	) (\r -> happyReturn (happyIn280 r))
10997
10998happyReduce_698 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
10999happyReduce_698 = happySpecReduce_1  265# happyReduction_698
11000happyReduction_698 happy_x_1
11001	 =  case happyOut315 happy_x_1 of { (HappyWrap315 happy_var_1) ->
11002	happyIn281
11003		 (happy_var_1
11004	)}
11005
11006happyReduce_699 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11007happyReduce_699 = happyMonadReduce 3# 265# happyReduction_699
11008happyReduction_699 (happy_x_3 `HappyStk`
11009	happy_x_2 `HappyStk`
11010	happy_x_1 `HappyStk`
11011	happyRest) tk
11012	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11013	case happyOut313 happy_x_2 of { (HappyWrap313 happy_var_2) ->
11014	case happyOutTok happy_x_3 of { happy_var_3 ->
11015	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11016                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11017                                       ,mj AnnBackquote happy_var_3])}}})
11018	) (\r -> happyReturn (happyIn281 r))
11019
11020happyReduce_700 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11021happyReduce_700 = happySpecReduce_1  266# happyReduction_700
11022happyReduction_700 happy_x_1
11023	 =  case happyOut283 happy_x_1 of { (HappyWrap283 happy_var_1) ->
11024	happyIn282
11025		 (happy_var_1
11026	)}
11027
11028happyReduce_701 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11029happyReduce_701 = happyMonadReduce 2# 266# happyReduction_701
11030happyReduction_701 (happy_x_2 `HappyStk`
11031	happy_x_1 `HappyStk`
11032	happyRest) tk
11033	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11034	case happyOutTok happy_x_2 of { happy_var_2 ->
11035	( ams (sLL happy_var_1 happy_var_2 $ getRdrName unitTyCon)
11036                                              [mop happy_var_1,mcp happy_var_2])}})
11037	) (\r -> happyReturn (happyIn282 r))
11038
11039happyReduce_702 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11040happyReduce_702 = happyMonadReduce 2# 266# happyReduction_702
11041happyReduction_702 (happy_x_2 `HappyStk`
11042	happy_x_1 `HappyStk`
11043	happyRest) tk
11044	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11045	case happyOutTok happy_x_2 of { happy_var_2 ->
11046	( ams (sLL happy_var_1 happy_var_2 $ getRdrName unboxedUnitTyCon)
11047                                              [mo happy_var_1,mc happy_var_2])}})
11048	) (\r -> happyReturn (happyIn282 r))
11049
11050happyReduce_703 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11051happyReduce_703 = happySpecReduce_1  267# happyReduction_703
11052happyReduction_703 happy_x_1
11053	 =  case happyOut284 happy_x_1 of { (HappyWrap284 happy_var_1) ->
11054	happyIn283
11055		 (happy_var_1
11056	)}
11057
11058happyReduce_704 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11059happyReduce_704 = happyMonadReduce 3# 267# happyReduction_704
11060happyReduction_704 (happy_x_3 `HappyStk`
11061	happy_x_2 `HappyStk`
11062	happy_x_1 `HappyStk`
11063	happyRest) tk
11064	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11065	case happyOut320 happy_x_2 of { (HappyWrap320 happy_var_2) ->
11066	case happyOutTok happy_x_3 of { happy_var_3 ->
11067	( ams (sLL happy_var_1 happy_var_3 $ getRdrName (tupleTyCon Boxed
11068                                                        (snd happy_var_2 + 1)))
11069                                       (mop happy_var_1:mcp happy_var_3:(mcommas (fst happy_var_2))))}}})
11070	) (\r -> happyReturn (happyIn283 r))
11071
11072happyReduce_705 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11073happyReduce_705 = happyMonadReduce 3# 267# happyReduction_705
11074happyReduction_705 (happy_x_3 `HappyStk`
11075	happy_x_2 `HappyStk`
11076	happy_x_1 `HappyStk`
11077	happyRest) tk
11078	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11079	case happyOut320 happy_x_2 of { (HappyWrap320 happy_var_2) ->
11080	case happyOutTok happy_x_3 of { happy_var_3 ->
11081	( ams (sLL happy_var_1 happy_var_3 $ getRdrName (tupleTyCon Unboxed
11082                                                        (snd happy_var_2 + 1)))
11083                                       (mo happy_var_1:mc happy_var_3:(mcommas (fst happy_var_2))))}}})
11084	) (\r -> happyReturn (happyIn283 r))
11085
11086happyReduce_706 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11087happyReduce_706 = happyMonadReduce 3# 267# happyReduction_706
11088happyReduction_706 (happy_x_3 `HappyStk`
11089	happy_x_2 `HappyStk`
11090	happy_x_1 `HappyStk`
11091	happyRest) tk
11092	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11093	case happyOutTok happy_x_2 of { happy_var_2 ->
11094	case happyOutTok happy_x_3 of { happy_var_3 ->
11095	( ams (sLL happy_var_1 happy_var_3 $ getRdrName funTyCon)
11096                                       [mop happy_var_1,mu AnnRarrow happy_var_2,mcp happy_var_3])}}})
11097	) (\r -> happyReturn (happyIn283 r))
11098
11099happyReduce_707 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11100happyReduce_707 = happyMonadReduce 2# 267# happyReduction_707
11101happyReduction_707 (happy_x_2 `HappyStk`
11102	happy_x_1 `HappyStk`
11103	happyRest) tk
11104	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11105	case happyOutTok happy_x_2 of { happy_var_2 ->
11106	( ams (sLL happy_var_1 happy_var_2 $ listTyCon_RDR) [mos happy_var_1,mcs happy_var_2])}})
11107	) (\r -> happyReturn (happyIn283 r))
11108
11109happyReduce_708 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11110happyReduce_708 = happySpecReduce_1  268# happyReduction_708
11111happyReduction_708 happy_x_1
11112	 =  case happyOut287 happy_x_1 of { (HappyWrap287 happy_var_1) ->
11113	happyIn284
11114		 (happy_var_1
11115	)}
11116
11117happyReduce_709 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11118happyReduce_709 = happyMonadReduce 3# 268# happyReduction_709
11119happyReduction_709 (happy_x_3 `HappyStk`
11120	happy_x_2 `HappyStk`
11121	happy_x_1 `HappyStk`
11122	happyRest) tk
11123	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11124	case happyOut290 happy_x_2 of { (HappyWrap290 happy_var_2) ->
11125	case happyOutTok happy_x_3 of { happy_var_3 ->
11126	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11127                                               [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
11128	) (\r -> happyReturn (happyIn284 r))
11129
11130happyReduce_710 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11131happyReduce_710 = happySpecReduce_1  269# happyReduction_710
11132happyReduction_710 happy_x_1
11133	 =  case happyOut287 happy_x_1 of { (HappyWrap287 happy_var_1) ->
11134	happyIn285
11135		 (happy_var_1
11136	)}
11137
11138happyReduce_711 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11139happyReduce_711 = happyMonadReduce 3# 269# happyReduction_711
11140happyReduction_711 (happy_x_3 `HappyStk`
11141	happy_x_2 `HappyStk`
11142	happy_x_1 `HappyStk`
11143	happyRest) tk
11144	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11145	case happyOutTok happy_x_2 of { happy_var_2 ->
11146	case happyOutTok happy_x_3 of { happy_var_3 ->
11147	( let { name :: Located RdrName
11148                                    ; name = sL1 happy_var_2 $! mkQual tcClsName (getQCONSYM happy_var_2) }
11149                                in ams (sLL happy_var_1 happy_var_3 (unLoc name)) [mop happy_var_1,mj AnnVal name,mcp happy_var_3])}}})
11150	) (\r -> happyReturn (happyIn285 r))
11151
11152happyReduce_712 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11153happyReduce_712 = happyMonadReduce 3# 269# happyReduction_712
11154happyReduction_712 (happy_x_3 `HappyStk`
11155	happy_x_2 `HappyStk`
11156	happy_x_1 `HappyStk`
11157	happyRest) tk
11158	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11159	case happyOutTok happy_x_2 of { happy_var_2 ->
11160	case happyOutTok happy_x_3 of { happy_var_3 ->
11161	( let { name :: Located RdrName
11162                                    ; name = sL1 happy_var_2 $! mkUnqual tcClsName (getCONSYM happy_var_2) }
11163                                in ams (sLL happy_var_1 happy_var_3 (unLoc name)) [mop happy_var_1,mj AnnVal name,mcp happy_var_3])}}})
11164	) (\r -> happyReturn (happyIn285 r))
11165
11166happyReduce_713 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11167happyReduce_713 = happyMonadReduce 3# 269# happyReduction_713
11168happyReduction_713 (happy_x_3 `HappyStk`
11169	happy_x_2 `HappyStk`
11170	happy_x_1 `HappyStk`
11171	happyRest) tk
11172	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11173	case happyOutTok happy_x_2 of { happy_var_2 ->
11174	case happyOutTok happy_x_3 of { happy_var_3 ->
11175	( let { name :: Located RdrName
11176                                    ; name = sL1 happy_var_2 $! consDataCon_RDR }
11177                                in ams (sLL happy_var_1 happy_var_3 (unLoc name)) [mop happy_var_1,mj AnnVal name,mcp happy_var_3])}}})
11178	) (\r -> happyReturn (happyIn285 r))
11179
11180happyReduce_714 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11181happyReduce_714 = happyMonadReduce 3# 269# happyReduction_714
11182happyReduction_714 (happy_x_3 `HappyStk`
11183	happy_x_2 `HappyStk`
11184	happy_x_1 `HappyStk`
11185	happyRest) tk
11186	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11187	case happyOutTok happy_x_2 of { happy_var_2 ->
11188	case happyOutTok happy_x_3 of { happy_var_3 ->
11189	( ams (sLL happy_var_1 happy_var_3 $ eqTyCon_RDR) [mop happy_var_1,mj AnnTilde happy_var_2,mcp happy_var_3])}}})
11190	) (\r -> happyReturn (happyIn285 r))
11191
11192happyReduce_715 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11193happyReduce_715 = happySpecReduce_1  270# happyReduction_715
11194happyReduction_715 happy_x_1
11195	 =  case happyOut290 happy_x_1 of { (HappyWrap290 happy_var_1) ->
11196	happyIn286
11197		 (happy_var_1
11198	)}
11199
11200happyReduce_716 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11201happyReduce_716 = happyMonadReduce 3# 270# happyReduction_716
11202happyReduction_716 (happy_x_3 `HappyStk`
11203	happy_x_2 `HappyStk`
11204	happy_x_1 `HappyStk`
11205	happyRest) tk
11206	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11207	case happyOut287 happy_x_2 of { (HappyWrap287 happy_var_2) ->
11208	case happyOutTok happy_x_3 of { happy_var_3 ->
11209	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11210                                               [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11211                                               ,mj AnnBackquote happy_var_3])}}})
11212	) (\r -> happyReturn (happyIn286 r))
11213
11214happyReduce_717 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11215happyReduce_717 = happySpecReduce_1  271# happyReduction_717
11216happyReduction_717 happy_x_1
11217	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11218	happyIn287
11219		 (sL1 happy_var_1 $! mkQual tcClsName (getQCONID happy_var_1)
11220	)}
11221
11222happyReduce_718 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11223happyReduce_718 = happySpecReduce_1  271# happyReduction_718
11224happyReduction_718 happy_x_1
11225	 =  case happyOut289 happy_x_1 of { (HappyWrap289 happy_var_1) ->
11226	happyIn287
11227		 (happy_var_1
11228	)}
11229
11230happyReduce_719 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11231happyReduce_719 = happySpecReduce_1  272# happyReduction_719
11232happyReduction_719 happy_x_1
11233	 =  case happyOut287 happy_x_1 of { (HappyWrap287 happy_var_1) ->
11234	happyIn288
11235		 (sL1 happy_var_1                           (HsTyVar noExtField NotPromoted happy_var_1)
11236	)}
11237
11238happyReduce_720 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11239happyReduce_720 = happySpecReduce_2  272# happyReduction_720
11240happyReduction_720 happy_x_2
11241	happy_x_1
11242	 =  case happyOut287 happy_x_1 of { (HappyWrap287 happy_var_1) ->
11243	case happyOut324 happy_x_2 of { (HappyWrap324 happy_var_2) ->
11244	happyIn288
11245		 (sLL happy_var_1 happy_var_2 (HsDocTy noExtField (sL1 happy_var_1 (HsTyVar noExtField NotPromoted happy_var_1)) happy_var_2)
11246	)}}
11247
11248happyReduce_721 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11249happyReduce_721 = happySpecReduce_1  273# happyReduction_721
11250happyReduction_721 happy_x_1
11251	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11252	happyIn289
11253		 (sL1 happy_var_1 $! mkUnqual tcClsName (getCONID happy_var_1)
11254	)}
11255
11256happyReduce_722 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11257happyReduce_722 = happySpecReduce_1  274# happyReduction_722
11258happyReduction_722 happy_x_1
11259	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11260	happyIn290
11261		 (sL1 happy_var_1 $! mkQual tcClsName (getQCONSYM happy_var_1)
11262	)}
11263
11264happyReduce_723 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11265happyReduce_723 = happySpecReduce_1  274# happyReduction_723
11266happyReduction_723 happy_x_1
11267	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11268	happyIn290
11269		 (sL1 happy_var_1 $! mkQual tcClsName (getQVARSYM happy_var_1)
11270	)}
11271
11272happyReduce_724 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11273happyReduce_724 = happySpecReduce_1  274# happyReduction_724
11274happyReduction_724 happy_x_1
11275	 =  case happyOut291 happy_x_1 of { (HappyWrap291 happy_var_1) ->
11276	happyIn290
11277		 (happy_var_1
11278	)}
11279
11280happyReduce_725 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11281happyReduce_725 = happySpecReduce_1  275# happyReduction_725
11282happyReduction_725 happy_x_1
11283	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11284	happyIn291
11285		 (sL1 happy_var_1 $! mkUnqual tcClsName (getCONSYM happy_var_1)
11286	)}
11287
11288happyReduce_726 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11289happyReduce_726 = happySpecReduce_1  275# happyReduction_726
11290happyReduction_726 happy_x_1
11291	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11292	happyIn291
11293		 (sL1 happy_var_1 $! mkUnqual tcClsName (getVARSYM happy_var_1)
11294	)}
11295
11296happyReduce_727 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11297happyReduce_727 = happySpecReduce_1  275# happyReduction_727
11298happyReduction_727 happy_x_1
11299	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11300	happyIn291
11301		 (sL1 happy_var_1 $! consDataCon_RDR
11302	)}
11303
11304happyReduce_728 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11305happyReduce_728 = happySpecReduce_1  275# happyReduction_728
11306happyReduction_728 happy_x_1
11307	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11308	happyIn291
11309		 (sL1 happy_var_1 $! mkUnqual tcClsName (fsLit "-")
11310	)}
11311
11312happyReduce_729 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11313happyReduce_729 = happySpecReduce_1  275# happyReduction_729
11314happyReduction_729 happy_x_1
11315	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11316	happyIn291
11317		 (sL1 happy_var_1 $! mkUnqual tcClsName (fsLit "!")
11318	)}
11319
11320happyReduce_730 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11321happyReduce_730 = happySpecReduce_1  275# happyReduction_730
11322happyReduction_730 happy_x_1
11323	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11324	happyIn291
11325		 (sL1 happy_var_1 $! mkUnqual tcClsName (fsLit ".")
11326	)}
11327
11328happyReduce_731 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11329happyReduce_731 = happySpecReduce_1  275# happyReduction_731
11330happyReduction_731 happy_x_1
11331	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11332	happyIn291
11333		 (sL1 happy_var_1 $ eqTyCon_RDR
11334	)}
11335
11336happyReduce_732 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11337happyReduce_732 = happySpecReduce_1  276# happyReduction_732
11338happyReduction_732 happy_x_1
11339	 =  case happyOut293 happy_x_1 of { (HappyWrap293 happy_var_1) ->
11340	happyIn292
11341		 (happy_var_1
11342	)}
11343
11344happyReduce_733 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11345happyReduce_733 = happySpecReduce_1  276# happyReduction_733
11346happyReduction_733 happy_x_1
11347	 =  case happyOut280 happy_x_1 of { (HappyWrap280 happy_var_1) ->
11348	happyIn292
11349		 (happy_var_1
11350	)}
11351
11352happyReduce_734 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11353happyReduce_734 = happySpecReduce_1  276# happyReduction_734
11354happyReduction_734 happy_x_1
11355	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11356	happyIn292
11357		 (sL1 happy_var_1 $ getRdrName funTyCon
11358	)}
11359
11360happyReduce_735 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11361happyReduce_735 = happySpecReduce_1  276# happyReduction_735
11362happyReduction_735 happy_x_1
11363	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11364	happyIn292
11365		 (sL1 happy_var_1 $ eqTyCon_RDR
11366	)}
11367
11368happyReduce_736 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11369happyReduce_736 = happySpecReduce_1  277# happyReduction_736
11370happyReduction_736 happy_x_1
11371	 =  case happyOut309 happy_x_1 of { (HappyWrap309 happy_var_1) ->
11372	happyIn293
11373		 (happy_var_1
11374	)}
11375
11376happyReduce_737 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11377happyReduce_737 = happyMonadReduce 3# 277# happyReduction_737
11378happyReduction_737 (happy_x_3 `HappyStk`
11379	happy_x_2 `HappyStk`
11380	happy_x_1 `HappyStk`
11381	happyRest) tk
11382	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11383	case happyOut305 happy_x_2 of { (HappyWrap305 happy_var_2) ->
11384	case happyOutTok happy_x_3 of { happy_var_3 ->
11385	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11386                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11387                                       ,mj AnnBackquote happy_var_3])}}})
11388	) (\r -> happyReturn (happyIn293 r))
11389
11390happyReduce_738 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11391happyReduce_738 = happySpecReduce_1  278# happyReduction_738
11392happyReduction_738 happy_x_1
11393	 =  case happyOut297 happy_x_1 of { (HappyWrap297 happy_var_1) ->
11394	happyIn294
11395		 (mkHsVarOpPV happy_var_1
11396	)}
11397
11398happyReduce_739 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11399happyReduce_739 = happySpecReduce_1  278# happyReduction_739
11400happyReduction_739 happy_x_1
11401	 =  case happyOut281 happy_x_1 of { (HappyWrap281 happy_var_1) ->
11402	happyIn294
11403		 (mkHsConOpPV happy_var_1
11404	)}
11405
11406happyReduce_740 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11407happyReduce_740 = happySpecReduce_1  278# happyReduction_740
11408happyReduction_740 happy_x_1
11409	 =  case happyOut296 happy_x_1 of { (HappyWrap296 happy_var_1) ->
11410	happyIn294
11411		 (happy_var_1
11412	)}
11413
11414happyReduce_741 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11415happyReduce_741 = happySpecReduce_1  279# happyReduction_741
11416happyReduction_741 happy_x_1
11417	 =  case happyOut298 happy_x_1 of { (HappyWrap298 happy_var_1) ->
11418	happyIn295
11419		 (mkHsVarOpPV happy_var_1
11420	)}
11421
11422happyReduce_742 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11423happyReduce_742 = happySpecReduce_1  279# happyReduction_742
11424happyReduction_742 happy_x_1
11425	 =  case happyOut281 happy_x_1 of { (HappyWrap281 happy_var_1) ->
11426	happyIn295
11427		 (mkHsConOpPV happy_var_1
11428	)}
11429
11430happyReduce_743 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11431happyReduce_743 = happySpecReduce_1  279# happyReduction_743
11432happyReduction_743 happy_x_1
11433	 =  case happyOut296 happy_x_1 of { (HappyWrap296 happy_var_1) ->
11434	happyIn295
11435		 (happy_var_1
11436	)}
11437
11438happyReduce_744 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11439happyReduce_744 = happySpecReduce_3  280# happyReduction_744
11440happyReduction_744 happy_x_3
11441	happy_x_2
11442	happy_x_1
11443	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11444	case happyOutTok happy_x_2 of { happy_var_2 ->
11445	case happyOutTok happy_x_3 of { happy_var_3 ->
11446	happyIn296
11447		 (amms (mkHsInfixHolePV (comb2 happy_var_1 happy_var_3))
11448                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11449                                       ,mj AnnBackquote happy_var_3]
11450	)}}}
11451
11452happyReduce_745 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11453happyReduce_745 = happySpecReduce_1  281# happyReduction_745
11454happyReduction_745 happy_x_1
11455	 =  case happyOut306 happy_x_1 of { (HappyWrap306 happy_var_1) ->
11456	happyIn297
11457		 (happy_var_1
11458	)}
11459
11460happyReduce_746 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11461happyReduce_746 = happyMonadReduce 3# 281# happyReduction_746
11462happyReduction_746 (happy_x_3 `HappyStk`
11463	happy_x_2 `HappyStk`
11464	happy_x_1 `HappyStk`
11465	happyRest) tk
11466	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11467	case happyOut304 happy_x_2 of { (HappyWrap304 happy_var_2) ->
11468	case happyOutTok happy_x_3 of { happy_var_3 ->
11469	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11470                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11471                                       ,mj AnnBackquote happy_var_3])}}})
11472	) (\r -> happyReturn (happyIn297 r))
11473
11474happyReduce_747 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11475happyReduce_747 = happySpecReduce_1  282# happyReduction_747
11476happyReduction_747 happy_x_1
11477	 =  case happyOut307 happy_x_1 of { (HappyWrap307 happy_var_1) ->
11478	happyIn298
11479		 (happy_var_1
11480	)}
11481
11482happyReduce_748 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11483happyReduce_748 = happyMonadReduce 3# 282# happyReduction_748
11484happyReduction_748 (happy_x_3 `HappyStk`
11485	happy_x_2 `HappyStk`
11486	happy_x_1 `HappyStk`
11487	happyRest) tk
11488	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11489	case happyOut304 happy_x_2 of { (HappyWrap304 happy_var_2) ->
11490	case happyOutTok happy_x_3 of { happy_var_3 ->
11491	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11492                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11493                                       ,mj AnnBackquote happy_var_3])}}})
11494	) (\r -> happyReturn (happyIn298 r))
11495
11496happyReduce_749 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11497happyReduce_749 = happySpecReduce_1  283# happyReduction_749
11498happyReduction_749 happy_x_1
11499	 =  case happyOut301 happy_x_1 of { (HappyWrap301 happy_var_1) ->
11500	happyIn299
11501		 (happy_var_1
11502	)}
11503
11504happyReduce_750 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11505happyReduce_750 = happyMonadReduce 3# 284# happyReduction_750
11506happyReduction_750 (happy_x_3 `HappyStk`
11507	happy_x_2 `HappyStk`
11508	happy_x_1 `HappyStk`
11509	happyRest) tk
11510	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11511	case happyOut301 happy_x_2 of { (HappyWrap301 happy_var_2) ->
11512	case happyOutTok happy_x_3 of { happy_var_3 ->
11513	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11514                                       [mj AnnBackquote happy_var_1,mj AnnVal happy_var_2
11515                                       ,mj AnnBackquote happy_var_3])}}})
11516	) (\r -> happyReturn (happyIn300 r))
11517
11518happyReduce_751 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11519happyReduce_751 = happySpecReduce_1  285# happyReduction_751
11520happyReduction_751 happy_x_1
11521	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11522	happyIn301
11523		 (sL1 happy_var_1 $! mkUnqual tvName (getVARID happy_var_1)
11524	)}
11525
11526happyReduce_752 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11527happyReduce_752 = happySpecReduce_1  285# happyReduction_752
11528happyReduction_752 happy_x_1
11529	 =  case happyOut311 happy_x_1 of { (HappyWrap311 happy_var_1) ->
11530	happyIn301
11531		 (sL1 happy_var_1 $! mkUnqual tvName (unLoc happy_var_1)
11532	)}
11533
11534happyReduce_753 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11535happyReduce_753 = happySpecReduce_1  285# happyReduction_753
11536happyReduction_753 happy_x_1
11537	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11538	happyIn301
11539		 (sL1 happy_var_1 $! mkUnqual tvName (fsLit "unsafe")
11540	)}
11541
11542happyReduce_754 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11543happyReduce_754 = happySpecReduce_1  285# happyReduction_754
11544happyReduction_754 happy_x_1
11545	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11546	happyIn301
11547		 (sL1 happy_var_1 $! mkUnqual tvName (fsLit "safe")
11548	)}
11549
11550happyReduce_755 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11551happyReduce_755 = happySpecReduce_1  285# happyReduction_755
11552happyReduction_755 happy_x_1
11553	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11554	happyIn301
11555		 (sL1 happy_var_1 $! mkUnqual tvName (fsLit "interruptible")
11556	)}
11557
11558happyReduce_756 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11559happyReduce_756 = happySpecReduce_1  286# happyReduction_756
11560happyReduction_756 happy_x_1
11561	 =  case happyOut305 happy_x_1 of { (HappyWrap305 happy_var_1) ->
11562	happyIn302
11563		 (happy_var_1
11564	)}
11565
11566happyReduce_757 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11567happyReduce_757 = happyMonadReduce 3# 286# happyReduction_757
11568happyReduction_757 (happy_x_3 `HappyStk`
11569	happy_x_2 `HappyStk`
11570	happy_x_1 `HappyStk`
11571	happyRest) tk
11572	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11573	case happyOut309 happy_x_2 of { (HappyWrap309 happy_var_2) ->
11574	case happyOutTok happy_x_3 of { happy_var_3 ->
11575	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11576                                       [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
11577	) (\r -> happyReturn (happyIn302 r))
11578
11579happyReduce_758 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11580happyReduce_758 = happySpecReduce_1  287# happyReduction_758
11581happyReduction_758 happy_x_1
11582	 =  case happyOut304 happy_x_1 of { (HappyWrap304 happy_var_1) ->
11583	happyIn303
11584		 (happy_var_1
11585	)}
11586
11587happyReduce_759 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11588happyReduce_759 = happyMonadReduce 3# 287# happyReduction_759
11589happyReduction_759 (happy_x_3 `HappyStk`
11590	happy_x_2 `HappyStk`
11591	happy_x_1 `HappyStk`
11592	happyRest) tk
11593	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11594	case happyOut309 happy_x_2 of { (HappyWrap309 happy_var_2) ->
11595	case happyOutTok happy_x_3 of { happy_var_3 ->
11596	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11597                                       [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
11598	) (\r -> happyReturn (happyIn303 r))
11599
11600happyReduce_760 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11601happyReduce_760 = happyMonadReduce 3# 287# happyReduction_760
11602happyReduction_760 (happy_x_3 `HappyStk`
11603	happy_x_2 `HappyStk`
11604	happy_x_1 `HappyStk`
11605	happyRest) tk
11606	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11607	case happyOut308 happy_x_2 of { (HappyWrap308 happy_var_2) ->
11608	case happyOutTok happy_x_3 of { happy_var_3 ->
11609	( ams (sLL happy_var_1 happy_var_3 (unLoc happy_var_2))
11610                                       [mop happy_var_1,mj AnnVal happy_var_2,mcp happy_var_3])}}})
11611	) (\r -> happyReturn (happyIn303 r))
11612
11613happyReduce_761 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11614happyReduce_761 = happySpecReduce_1  288# happyReduction_761
11615happyReduction_761 happy_x_1
11616	 =  case happyOut305 happy_x_1 of { (HappyWrap305 happy_var_1) ->
11617	happyIn304
11618		 (happy_var_1
11619	)}
11620
11621happyReduce_762 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11622happyReduce_762 = happySpecReduce_1  288# happyReduction_762
11623happyReduction_762 happy_x_1
11624	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11625	happyIn304
11626		 (sL1 happy_var_1 $! mkQual varName (getQVARID happy_var_1)
11627	)}
11628
11629happyReduce_763 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11630happyReduce_763 = happySpecReduce_1  289# happyReduction_763
11631happyReduction_763 happy_x_1
11632	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11633	happyIn305
11634		 (sL1 happy_var_1 $! mkUnqual varName (getVARID happy_var_1)
11635	)}
11636
11637happyReduce_764 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11638happyReduce_764 = happySpecReduce_1  289# happyReduction_764
11639happyReduction_764 happy_x_1
11640	 =  case happyOut311 happy_x_1 of { (HappyWrap311 happy_var_1) ->
11641	happyIn305
11642		 (sL1 happy_var_1 $! mkUnqual varName (unLoc happy_var_1)
11643	)}
11644
11645happyReduce_765 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11646happyReduce_765 = happySpecReduce_1  289# happyReduction_765
11647happyReduction_765 happy_x_1
11648	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11649	happyIn305
11650		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "unsafe")
11651	)}
11652
11653happyReduce_766 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11654happyReduce_766 = happySpecReduce_1  289# happyReduction_766
11655happyReduction_766 happy_x_1
11656	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11657	happyIn305
11658		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "safe")
11659	)}
11660
11661happyReduce_767 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11662happyReduce_767 = happySpecReduce_1  289# happyReduction_767
11663happyReduction_767 happy_x_1
11664	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11665	happyIn305
11666		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "interruptible")
11667	)}
11668
11669happyReduce_768 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11670happyReduce_768 = happySpecReduce_1  289# happyReduction_768
11671happyReduction_768 happy_x_1
11672	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11673	happyIn305
11674		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "forall")
11675	)}
11676
11677happyReduce_769 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11678happyReduce_769 = happySpecReduce_1  289# happyReduction_769
11679happyReduction_769 happy_x_1
11680	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11681	happyIn305
11682		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "family")
11683	)}
11684
11685happyReduce_770 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11686happyReduce_770 = happySpecReduce_1  289# happyReduction_770
11687happyReduction_770 happy_x_1
11688	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11689	happyIn305
11690		 (sL1 happy_var_1 $! mkUnqual varName (fsLit "role")
11691	)}
11692
11693happyReduce_771 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11694happyReduce_771 = happySpecReduce_1  290# happyReduction_771
11695happyReduction_771 happy_x_1
11696	 =  case happyOut309 happy_x_1 of { (HappyWrap309 happy_var_1) ->
11697	happyIn306
11698		 (happy_var_1
11699	)}
11700
11701happyReduce_772 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11702happyReduce_772 = happySpecReduce_1  290# happyReduction_772
11703happyReduction_772 happy_x_1
11704	 =  case happyOut308 happy_x_1 of { (HappyWrap308 happy_var_1) ->
11705	happyIn306
11706		 (happy_var_1
11707	)}
11708
11709happyReduce_773 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11710happyReduce_773 = happySpecReduce_1  291# happyReduction_773
11711happyReduction_773 happy_x_1
11712	 =  case happyOut310 happy_x_1 of { (HappyWrap310 happy_var_1) ->
11713	happyIn307
11714		 (happy_var_1
11715	)}
11716
11717happyReduce_774 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11718happyReduce_774 = happySpecReduce_1  291# happyReduction_774
11719happyReduction_774 happy_x_1
11720	 =  case happyOut308 happy_x_1 of { (HappyWrap308 happy_var_1) ->
11721	happyIn307
11722		 (happy_var_1
11723	)}
11724
11725happyReduce_775 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11726happyReduce_775 = happySpecReduce_1  292# happyReduction_775
11727happyReduction_775 happy_x_1
11728	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11729	happyIn308
11730		 (sL1 happy_var_1 $ mkQual varName (getQVARSYM happy_var_1)
11731	)}
11732
11733happyReduce_776 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11734happyReduce_776 = happySpecReduce_1  293# happyReduction_776
11735happyReduction_776 happy_x_1
11736	 =  case happyOut310 happy_x_1 of { (HappyWrap310 happy_var_1) ->
11737	happyIn309
11738		 (happy_var_1
11739	)}
11740
11741happyReduce_777 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11742happyReduce_777 = happySpecReduce_1  293# happyReduction_777
11743happyReduction_777 happy_x_1
11744	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11745	happyIn309
11746		 (sL1 happy_var_1 $ mkUnqual varName (fsLit "-")
11747	)}
11748
11749happyReduce_778 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11750happyReduce_778 = happySpecReduce_1  294# happyReduction_778
11751happyReduction_778 happy_x_1
11752	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11753	happyIn310
11754		 (sL1 happy_var_1 $ mkUnqual varName (getVARSYM happy_var_1)
11755	)}
11756
11757happyReduce_779 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11758happyReduce_779 = happySpecReduce_1  294# happyReduction_779
11759happyReduction_779 happy_x_1
11760	 =  case happyOut312 happy_x_1 of { (HappyWrap312 happy_var_1) ->
11761	happyIn310
11762		 (sL1 happy_var_1 $ mkUnqual varName (unLoc happy_var_1)
11763	)}
11764
11765happyReduce_780 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11766happyReduce_780 = happySpecReduce_1  295# happyReduction_780
11767happyReduction_780 happy_x_1
11768	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11769	happyIn311
11770		 (sL1 happy_var_1 (fsLit "as")
11771	)}
11772
11773happyReduce_781 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11774happyReduce_781 = happySpecReduce_1  295# happyReduction_781
11775happyReduction_781 happy_x_1
11776	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11777	happyIn311
11778		 (sL1 happy_var_1 (fsLit "qualified")
11779	)}
11780
11781happyReduce_782 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11782happyReduce_782 = happySpecReduce_1  295# happyReduction_782
11783happyReduction_782 happy_x_1
11784	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11785	happyIn311
11786		 (sL1 happy_var_1 (fsLit "hiding")
11787	)}
11788
11789happyReduce_783 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11790happyReduce_783 = happySpecReduce_1  295# happyReduction_783
11791happyReduction_783 happy_x_1
11792	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11793	happyIn311
11794		 (sL1 happy_var_1 (fsLit "export")
11795	)}
11796
11797happyReduce_784 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11798happyReduce_784 = happySpecReduce_1  295# happyReduction_784
11799happyReduction_784 happy_x_1
11800	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11801	happyIn311
11802		 (sL1 happy_var_1 (fsLit "label")
11803	)}
11804
11805happyReduce_785 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11806happyReduce_785 = happySpecReduce_1  295# happyReduction_785
11807happyReduction_785 happy_x_1
11808	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11809	happyIn311
11810		 (sL1 happy_var_1 (fsLit "dynamic")
11811	)}
11812
11813happyReduce_786 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11814happyReduce_786 = happySpecReduce_1  295# happyReduction_786
11815happyReduction_786 happy_x_1
11816	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11817	happyIn311
11818		 (sL1 happy_var_1 (fsLit "stdcall")
11819	)}
11820
11821happyReduce_787 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11822happyReduce_787 = happySpecReduce_1  295# happyReduction_787
11823happyReduction_787 happy_x_1
11824	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11825	happyIn311
11826		 (sL1 happy_var_1 (fsLit "ccall")
11827	)}
11828
11829happyReduce_788 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11830happyReduce_788 = happySpecReduce_1  295# happyReduction_788
11831happyReduction_788 happy_x_1
11832	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11833	happyIn311
11834		 (sL1 happy_var_1 (fsLit "capi")
11835	)}
11836
11837happyReduce_789 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11838happyReduce_789 = happySpecReduce_1  295# happyReduction_789
11839happyReduction_789 happy_x_1
11840	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11841	happyIn311
11842		 (sL1 happy_var_1 (fsLit "prim")
11843	)}
11844
11845happyReduce_790 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11846happyReduce_790 = happySpecReduce_1  295# happyReduction_790
11847happyReduction_790 happy_x_1
11848	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11849	happyIn311
11850		 (sL1 happy_var_1 (fsLit "javascript")
11851	)}
11852
11853happyReduce_791 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11854happyReduce_791 = happySpecReduce_1  295# happyReduction_791
11855happyReduction_791 happy_x_1
11856	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11857	happyIn311
11858		 (sL1 happy_var_1 (fsLit "group")
11859	)}
11860
11861happyReduce_792 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11862happyReduce_792 = happySpecReduce_1  295# happyReduction_792
11863happyReduction_792 happy_x_1
11864	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11865	happyIn311
11866		 (sL1 happy_var_1 (fsLit "stock")
11867	)}
11868
11869happyReduce_793 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11870happyReduce_793 = happySpecReduce_1  295# happyReduction_793
11871happyReduction_793 happy_x_1
11872	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11873	happyIn311
11874		 (sL1 happy_var_1 (fsLit "anyclass")
11875	)}
11876
11877happyReduce_794 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11878happyReduce_794 = happySpecReduce_1  295# happyReduction_794
11879happyReduction_794 happy_x_1
11880	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11881	happyIn311
11882		 (sL1 happy_var_1 (fsLit "via")
11883	)}
11884
11885happyReduce_795 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11886happyReduce_795 = happySpecReduce_1  295# happyReduction_795
11887happyReduction_795 happy_x_1
11888	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11889	happyIn311
11890		 (sL1 happy_var_1 (fsLit "unit")
11891	)}
11892
11893happyReduce_796 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11894happyReduce_796 = happySpecReduce_1  295# happyReduction_796
11895happyReduction_796 happy_x_1
11896	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11897	happyIn311
11898		 (sL1 happy_var_1 (fsLit "dependency")
11899	)}
11900
11901happyReduce_797 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11902happyReduce_797 = happySpecReduce_1  295# happyReduction_797
11903happyReduction_797 happy_x_1
11904	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11905	happyIn311
11906		 (sL1 happy_var_1 (fsLit "signature")
11907	)}
11908
11909happyReduce_798 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11910happyReduce_798 = happyMonadReduce 1# 296# happyReduction_798
11911happyReduction_798 (happy_x_1 `HappyStk`
11912	happyRest) tk
11913	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
11914	( ams (sL1 happy_var_1 (fsLit "!")) [mj AnnBang happy_var_1])})
11915	) (\r -> happyReturn (happyIn312 r))
11916
11917happyReduce_799 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11918happyReduce_799 = happySpecReduce_1  296# happyReduction_799
11919happyReduction_799 happy_x_1
11920	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11921	happyIn312
11922		 (sL1 happy_var_1 (fsLit ".")
11923	)}
11924
11925happyReduce_800 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11926happyReduce_800 = happySpecReduce_1  296# happyReduction_800
11927happyReduction_800 happy_x_1
11928	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11929	happyIn312
11930		 (sL1 happy_var_1 (fsLit (starSym (isUnicode happy_var_1)))
11931	)}
11932
11933happyReduce_801 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11934happyReduce_801 = happySpecReduce_1  297# happyReduction_801
11935happyReduction_801 happy_x_1
11936	 =  case happyOut314 happy_x_1 of { (HappyWrap314 happy_var_1) ->
11937	happyIn313
11938		 (happy_var_1
11939	)}
11940
11941happyReduce_802 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11942happyReduce_802 = happySpecReduce_1  297# happyReduction_802
11943happyReduction_802 happy_x_1
11944	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11945	happyIn313
11946		 (sL1 happy_var_1 $! mkQual dataName (getQCONID happy_var_1)
11947	)}
11948
11949happyReduce_803 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11950happyReduce_803 = happySpecReduce_1  298# happyReduction_803
11951happyReduction_803 happy_x_1
11952	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11953	happyIn314
11954		 (sL1 happy_var_1 $ mkUnqual dataName (getCONID happy_var_1)
11955	)}
11956
11957happyReduce_804 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11958happyReduce_804 = happySpecReduce_1  299# happyReduction_804
11959happyReduction_804 happy_x_1
11960	 =  case happyOut316 happy_x_1 of { (HappyWrap316 happy_var_1) ->
11961	happyIn315
11962		 (happy_var_1
11963	)}
11964
11965happyReduce_805 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11966happyReduce_805 = happySpecReduce_1  299# happyReduction_805
11967happyReduction_805 happy_x_1
11968	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11969	happyIn315
11970		 (sL1 happy_var_1 $ mkQual dataName (getQCONSYM happy_var_1)
11971	)}
11972
11973happyReduce_806 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11974happyReduce_806 = happySpecReduce_1  300# happyReduction_806
11975happyReduction_806 happy_x_1
11976	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11977	happyIn316
11978		 (sL1 happy_var_1 $ mkUnqual dataName (getCONSYM happy_var_1)
11979	)}
11980
11981happyReduce_807 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11982happyReduce_807 = happySpecReduce_1  300# happyReduction_807
11983happyReduction_807 happy_x_1
11984	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11985	happyIn316
11986		 (sL1 happy_var_1 $ consDataCon_RDR
11987	)}
11988
11989happyReduce_808 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11990happyReduce_808 = happySpecReduce_1  301# happyReduction_808
11991happyReduction_808 happy_x_1
11992	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
11993	happyIn317
11994		 (sL1 happy_var_1 $ HsChar       (getCHARs happy_var_1) $ getCHAR happy_var_1
11995	)}
11996
11997happyReduce_809 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
11998happyReduce_809 = happySpecReduce_1  301# happyReduction_809
11999happyReduction_809 happy_x_1
12000	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12001	happyIn317
12002		 (sL1 happy_var_1 $ HsString     (getSTRINGs happy_var_1)
12003                                                    $ getSTRING happy_var_1
12004	)}
12005
12006happyReduce_810 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12007happyReduce_810 = happySpecReduce_1  301# happyReduction_810
12008happyReduction_810 happy_x_1
12009	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12010	happyIn317
12011		 (sL1 happy_var_1 $ HsIntPrim    (getPRIMINTEGERs happy_var_1)
12012                                                    $ getPRIMINTEGER happy_var_1
12013	)}
12014
12015happyReduce_811 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12016happyReduce_811 = happySpecReduce_1  301# happyReduction_811
12017happyReduction_811 happy_x_1
12018	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12019	happyIn317
12020		 (sL1 happy_var_1 $ HsWordPrim   (getPRIMWORDs happy_var_1)
12021                                                    $ getPRIMWORD happy_var_1
12022	)}
12023
12024happyReduce_812 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12025happyReduce_812 = happySpecReduce_1  301# happyReduction_812
12026happyReduction_812 happy_x_1
12027	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12028	happyIn317
12029		 (sL1 happy_var_1 $ HsCharPrim   (getPRIMCHARs happy_var_1)
12030                                                    $ getPRIMCHAR happy_var_1
12031	)}
12032
12033happyReduce_813 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12034happyReduce_813 = happySpecReduce_1  301# happyReduction_813
12035happyReduction_813 happy_x_1
12036	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12037	happyIn317
12038		 (sL1 happy_var_1 $ HsStringPrim (getPRIMSTRINGs happy_var_1)
12039                                                    $ getPRIMSTRING happy_var_1
12040	)}
12041
12042happyReduce_814 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12043happyReduce_814 = happySpecReduce_1  301# happyReduction_814
12044happyReduction_814 happy_x_1
12045	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12046	happyIn317
12047		 (sL1 happy_var_1 $ HsFloatPrim  noExtField $ getPRIMFLOAT happy_var_1
12048	)}
12049
12050happyReduce_815 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12051happyReduce_815 = happySpecReduce_1  301# happyReduction_815
12052happyReduction_815 happy_x_1
12053	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12054	happyIn317
12055		 (sL1 happy_var_1 $ HsDoublePrim noExtField $ getPRIMDOUBLE happy_var_1
12056	)}
12057
12058happyReduce_816 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12059happyReduce_816 = happySpecReduce_1  302# happyReduction_816
12060happyReduction_816 happy_x_1
12061	 =  happyIn318
12062		 (()
12063	)
12064
12065happyReduce_817 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12066happyReduce_817 = happyMonadReduce 1# 302# happyReduction_817
12067happyReduction_817 (happy_x_1 `HappyStk`
12068	happyRest) tk
12069	 = happyThen ((( popContext))
12070	) (\r -> happyReturn (happyIn318 r))
12071
12072happyReduce_818 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12073happyReduce_818 = happySpecReduce_1  303# happyReduction_818
12074happyReduction_818 happy_x_1
12075	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12076	happyIn319
12077		 (sL1 happy_var_1 $ mkModuleNameFS (getCONID happy_var_1)
12078	)}
12079
12080happyReduce_819 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12081happyReduce_819 = happySpecReduce_1  303# happyReduction_819
12082happyReduction_819 happy_x_1
12083	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12084	happyIn319
12085		 (sL1 happy_var_1 $ let (mod,c) = getQCONID happy_var_1 in
12086                                  mkModuleNameFS
12087                                   (mkFastString
12088                                     (unpackFS mod ++ '.':unpackFS c))
12089	)}
12090
12091happyReduce_820 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12092happyReduce_820 = happySpecReduce_2  304# happyReduction_820
12093happyReduction_820 happy_x_2
12094	happy_x_1
12095	 =  case happyOut320 happy_x_1 of { (HappyWrap320 happy_var_1) ->
12096	case happyOutTok happy_x_2 of { happy_var_2 ->
12097	happyIn320
12098		 (((fst happy_var_1)++[gl happy_var_2],snd happy_var_1 + 1)
12099	)}}
12100
12101happyReduce_821 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12102happyReduce_821 = happySpecReduce_1  304# happyReduction_821
12103happyReduction_821 happy_x_1
12104	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12105	happyIn320
12106		 (([gl happy_var_1],1)
12107	)}
12108
12109happyReduce_822 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12110happyReduce_822 = happySpecReduce_1  305# happyReduction_822
12111happyReduction_822 happy_x_1
12112	 =  case happyOut322 happy_x_1 of { (HappyWrap322 happy_var_1) ->
12113	happyIn321
12114		 (happy_var_1
12115	)}
12116
12117happyReduce_823 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12118happyReduce_823 = happySpecReduce_0  305# happyReduction_823
12119happyReduction_823  =  happyIn321
12120		 (([], 0)
12121	)
12122
12123happyReduce_824 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12124happyReduce_824 = happySpecReduce_2  306# happyReduction_824
12125happyReduction_824 happy_x_2
12126	happy_x_1
12127	 =  case happyOut322 happy_x_1 of { (HappyWrap322 happy_var_1) ->
12128	case happyOutTok happy_x_2 of { happy_var_2 ->
12129	happyIn322
12130		 (((fst happy_var_1)++[gl happy_var_2],snd happy_var_1 + 1)
12131	)}}
12132
12133happyReduce_825 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12134happyReduce_825 = happySpecReduce_1  306# happyReduction_825
12135happyReduction_825 happy_x_1
12136	 =  case happyOutTok happy_x_1 of { happy_var_1 ->
12137	happyIn322
12138		 (([gl happy_var_1],1)
12139	)}
12140
12141happyReduce_826 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12142happyReduce_826 = happyMonadReduce 1# 307# happyReduction_826
12143happyReduction_826 (happy_x_1 `HappyStk`
12144	happyRest) tk
12145	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
12146	( return (sL1 happy_var_1 (mkHsDocString (getDOCNEXT happy_var_1))))})
12147	) (\r -> happyReturn (happyIn323 r))
12148
12149happyReduce_827 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12150happyReduce_827 = happyMonadReduce 1# 308# happyReduction_827
12151happyReduction_827 (happy_x_1 `HappyStk`
12152	happyRest) tk
12153	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
12154	( return (sL1 happy_var_1 (mkHsDocString (getDOCPREV happy_var_1))))})
12155	) (\r -> happyReturn (happyIn324 r))
12156
12157happyReduce_828 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12158happyReduce_828 = happyMonadReduce 1# 309# happyReduction_828
12159happyReduction_828 (happy_x_1 `HappyStk`
12160	happyRest) tk
12161	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
12162	(
12163      let string = getDOCNAMED happy_var_1
12164          (name, rest) = break isSpace string
12165      in return (sL1 happy_var_1 (name, mkHsDocString rest)))})
12166	) (\r -> happyReturn (happyIn325 r))
12167
12168happyReduce_829 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12169happyReduce_829 = happyMonadReduce 1# 310# happyReduction_829
12170happyReduction_829 (happy_x_1 `HappyStk`
12171	happyRest) tk
12172	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
12173	( let (n, doc) = getDOCSECTION happy_var_1 in
12174        return (sL1 happy_var_1 (n, mkHsDocString doc)))})
12175	) (\r -> happyReturn (happyIn326 r))
12176
12177happyReduce_830 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12178happyReduce_830 = happyMonadReduce 1# 311# happyReduction_830
12179happyReduction_830 (happy_x_1 `HappyStk`
12180	happyRest) tk
12181	 = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
12182	( let string = getDOCNEXT happy_var_1 in
12183                     return (Just (sL1 happy_var_1 (mkHsDocString string))))})
12184	) (\r -> happyReturn (happyIn327 r))
12185
12186happyReduce_831 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12187happyReduce_831 = happySpecReduce_1  312# happyReduction_831
12188happyReduction_831 happy_x_1
12189	 =  case happyOut324 happy_x_1 of { (HappyWrap324 happy_var_1) ->
12190	happyIn328
12191		 (Just happy_var_1
12192	)}
12193
12194happyReduce_832 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12195happyReduce_832 = happySpecReduce_0  312# happyReduction_832
12196happyReduction_832  =  happyIn328
12197		 (Nothing
12198	)
12199
12200happyReduce_833 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12201happyReduce_833 = happySpecReduce_1  313# happyReduction_833
12202happyReduction_833 happy_x_1
12203	 =  case happyOut323 happy_x_1 of { (HappyWrap323 happy_var_1) ->
12204	happyIn329
12205		 (Just happy_var_1
12206	)}
12207
12208happyReduce_834 :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12209happyReduce_834 = happySpecReduce_0  313# happyReduction_834
12210happyReduction_834  =  happyIn329
12211		 (Nothing
12212	)
12213
12214happyNewToken action sts stk
12215	= (lexer True)(\tk ->
12216	let cont i = happyDoAction i tk action sts stk in
12217	case tk of {
12218	L _ ITeof -> happyDoAction 153# tk action sts stk;
12219	L _ ITunderscore -> cont 1#;
12220	L _ ITas -> cont 2#;
12221	L _ ITcase -> cont 3#;
12222	L _ ITclass -> cont 4#;
12223	L _ ITdata -> cont 5#;
12224	L _ ITdefault -> cont 6#;
12225	L _ ITderiving -> cont 7#;
12226	L _ ITdo -> cont 8#;
12227	L _ ITelse -> cont 9#;
12228	L _ IThiding -> cont 10#;
12229	L _ ITif -> cont 11#;
12230	L _ ITimport -> cont 12#;
12231	L _ ITin -> cont 13#;
12232	L _ ITinfix -> cont 14#;
12233	L _ ITinfixl -> cont 15#;
12234	L _ ITinfixr -> cont 16#;
12235	L _ ITinstance -> cont 17#;
12236	L _ ITlet -> cont 18#;
12237	L _ ITmodule -> cont 19#;
12238	L _ ITnewtype -> cont 20#;
12239	L _ ITof -> cont 21#;
12240	L _ ITqualified -> cont 22#;
12241	L _ ITthen -> cont 23#;
12242	L _ ITtype -> cont 24#;
12243	L _ ITwhere -> cont 25#;
12244	L _ (ITforall _) -> cont 26#;
12245	L _ ITforeign -> cont 27#;
12246	L _ ITexport -> cont 28#;
12247	L _ ITlabel -> cont 29#;
12248	L _ ITdynamic -> cont 30#;
12249	L _ ITsafe -> cont 31#;
12250	L _ ITinterruptible -> cont 32#;
12251	L _ ITunsafe -> cont 33#;
12252	L _ ITmdo -> cont 34#;
12253	L _ ITfamily -> cont 35#;
12254	L _ ITrole -> cont 36#;
12255	L _ ITstdcallconv -> cont 37#;
12256	L _ ITccallconv -> cont 38#;
12257	L _ ITcapiconv -> cont 39#;
12258	L _ ITprimcallconv -> cont 40#;
12259	L _ ITjavascriptcallconv -> cont 41#;
12260	L _ ITproc -> cont 42#;
12261	L _ ITrec -> cont 43#;
12262	L _ ITgroup -> cont 44#;
12263	L _ ITby -> cont 45#;
12264	L _ ITusing -> cont 46#;
12265	L _ ITpattern -> cont 47#;
12266	L _ ITstatic -> cont 48#;
12267	L _ ITstock -> cont 49#;
12268	L _ ITanyclass -> cont 50#;
12269	L _ ITvia -> cont 51#;
12270	L _ ITunit -> cont 52#;
12271	L _ ITsignature -> cont 53#;
12272	L _ ITdependency -> cont 54#;
12273	L _ (ITinline_prag _ _ _) -> cont 55#;
12274	L _ (ITspec_prag _) -> cont 56#;
12275	L _ (ITspec_inline_prag _ _) -> cont 57#;
12276	L _ (ITsource_prag _) -> cont 58#;
12277	L _ (ITrules_prag _) -> cont 59#;
12278	L _ (ITcore_prag _) -> cont 60#;
12279	L _ (ITscc_prag _) -> cont 61#;
12280	L _ (ITgenerated_prag _) -> cont 62#;
12281	L _ (ITdeprecated_prag _) -> cont 63#;
12282	L _ (ITwarning_prag _) -> cont 64#;
12283	L _ (ITunpack_prag _) -> cont 65#;
12284	L _ (ITnounpack_prag _) -> cont 66#;
12285	L _ (ITann_prag _) -> cont 67#;
12286	L _ (ITminimal_prag _) -> cont 68#;
12287	L _ (ITctype _) -> cont 69#;
12288	L _ (IToverlapping_prag _) -> cont 70#;
12289	L _ (IToverlappable_prag _) -> cont 71#;
12290	L _ (IToverlaps_prag _) -> cont 72#;
12291	L _ (ITincoherent_prag _) -> cont 73#;
12292	L _ (ITcomplete_prag _) -> cont 74#;
12293	L _ ITclose_prag -> cont 75#;
12294	L _ ITdotdot -> cont 76#;
12295	L _ ITcolon -> cont 77#;
12296	L _ (ITdcolon _) -> cont 78#;
12297	L _ ITequal -> cont 79#;
12298	L _ ITlam -> cont 80#;
12299	L _ ITlcase -> cont 81#;
12300	L _ ITvbar -> cont 82#;
12301	L _ (ITlarrow _) -> cont 83#;
12302	L _ (ITrarrow _) -> cont 84#;
12303	L _ ITat -> cont 85#;
12304	L _ ITtilde -> cont 86#;
12305	L _ (ITdarrow _) -> cont 87#;
12306	L _ ITminus -> cont 88#;
12307	L _ ITbang -> cont 89#;
12308	L _ (ITstar _) -> cont 90#;
12309	L _ (ITlarrowtail _) -> cont 91#;
12310	L _ (ITrarrowtail _) -> cont 92#;
12311	L _ (ITLarrowtail _) -> cont 93#;
12312	L _ (ITRarrowtail _) -> cont 94#;
12313	L _ ITdot -> cont 95#;
12314	L _ ITtypeApp -> cont 96#;
12315	L _ ITocurly -> cont 97#;
12316	L _ ITccurly -> cont 98#;
12317	L _ ITvocurly -> cont 99#;
12318	L _ ITvccurly -> cont 100#;
12319	L _ ITobrack -> cont 101#;
12320	L _ ITcbrack -> cont 102#;
12321	L _ ITopabrack -> cont 103#;
12322	L _ ITcpabrack -> cont 104#;
12323	L _ IToparen -> cont 105#;
12324	L _ ITcparen -> cont 106#;
12325	L _ IToubxparen -> cont 107#;
12326	L _ ITcubxparen -> cont 108#;
12327	L _ (IToparenbar _) -> cont 109#;
12328	L _ (ITcparenbar _) -> cont 110#;
12329	L _ ITsemi -> cont 111#;
12330	L _ ITcomma -> cont 112#;
12331	L _ ITbackquote -> cont 113#;
12332	L _ ITsimpleQuote -> cont 114#;
12333	L _ (ITvarid    _) -> cont 115#;
12334	L _ (ITconid    _) -> cont 116#;
12335	L _ (ITvarsym   _) -> cont 117#;
12336	L _ (ITconsym   _) -> cont 118#;
12337	L _ (ITqvarid   _) -> cont 119#;
12338	L _ (ITqconid   _) -> cont 120#;
12339	L _ (ITqvarsym  _) -> cont 121#;
12340	L _ (ITqconsym  _) -> cont 122#;
12341	L _ (ITdupipvarid   _) -> cont 123#;
12342	L _ (ITlabelvarid   _) -> cont 124#;
12343	L _ (ITchar   _ _) -> cont 125#;
12344	L _ (ITstring _ _) -> cont 126#;
12345	L _ (ITinteger _) -> cont 127#;
12346	L _ (ITrational _) -> cont 128#;
12347	L _ (ITprimchar   _ _) -> cont 129#;
12348	L _ (ITprimstring _ _) -> cont 130#;
12349	L _ (ITprimint    _ _) -> cont 131#;
12350	L _ (ITprimword   _ _) -> cont 132#;
12351	L _ (ITprimfloat  _) -> cont 133#;
12352	L _ (ITprimdouble _) -> cont 134#;
12353	L _ (ITdocCommentNext _) -> cont 135#;
12354	L _ (ITdocCommentPrev _) -> cont 136#;
12355	L _ (ITdocCommentNamed _) -> cont 137#;
12356	L _ (ITdocSection _ _) -> cont 138#;
12357	L _ (ITopenExpQuote _ _) -> cont 139#;
12358	L _ ITopenPatQuote -> cont 140#;
12359	L _ ITopenTypQuote -> cont 141#;
12360	L _ ITopenDecQuote -> cont 142#;
12361	L _ (ITcloseQuote _) -> cont 143#;
12362	L _ (ITopenTExpQuote _) -> cont 144#;
12363	L _ ITcloseTExpQuote -> cont 145#;
12364	L _ (ITidEscape _) -> cont 146#;
12365	L _ ITparenEscape -> cont 147#;
12366	L _ (ITidTyEscape _) -> cont 148#;
12367	L _ ITparenTyEscape -> cont 149#;
12368	L _ ITtyQuote -> cont 150#;
12369	L _ (ITquasiQuote _) -> cont 151#;
12370	L _ (ITqQuasiQuote _) -> cont 152#;
12371	_ -> happyError' (tk, [])
12372	})
12373
12374happyError_ explist 153# tk = happyError' (tk, explist)
12375happyError_ explist _ tk = happyError' (tk, explist)
12376
12377happyThen :: () => P a -> (a -> P b) -> P b
12378happyThen = (>>=)
12379happyReturn :: () => a -> P a
12380happyReturn = (return)
12381happyParse :: () => Happy_GHC_Exts.Int# -> P (HappyAbsSyn )
12382
12383happyNewToken :: () => Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12384
12385happyDoAction :: () => Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn )
12386
12387happyReduceArr :: () => Happy_Data_Array.Array Int (Happy_GHC_Exts.Int# -> (Located Token) -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn ) -> P (HappyAbsSyn ))
12388
12389happyThen1 :: () => P a -> (a -> P b) -> P b
12390happyThen1 = happyThen
12391happyReturn1 :: () => a -> P a
12392happyReturn1 = happyReturn
12393happyError' :: () => (((Located Token)), [String]) -> P a
12394happyError' tk = (\(tokens, explist) -> happyError) tk
12395parseModule = happySomeParser where
12396 happySomeParser = happyThen (happyParse 0#) (\x -> happyReturn (let {(HappyWrap34 x') = happyOut34 x} in x'))
12397
12398parseSignature = happySomeParser where
12399 happySomeParser = happyThen (happyParse 1#) (\x -> happyReturn (let {(HappyWrap33 x') = happyOut33 x} in x'))
12400
12401parseImport = happySomeParser where
12402 happySomeParser = happyThen (happyParse 2#) (\x -> happyReturn (let {(HappyWrap64 x') = happyOut64 x} in x'))
12403
12404parseStatement = happySomeParser where
12405 happySomeParser = happyThen (happyParse 3#) (\x -> happyReturn (let {(HappyWrap256 x') = happyOut256 x} in x'))
12406
12407parseDeclaration = happySomeParser where
12408 happySomeParser = happyThen (happyParse 4#) (\x -> happyReturn (let {(HappyWrap77 x') = happyOut77 x} in x'))
12409
12410parseExpression = happySomeParser where
12411 happySomeParser = happyThen (happyParse 5#) (\x -> happyReturn (let {(HappyWrap209 x') = happyOut209 x} in x'))
12412
12413parsePattern = happySomeParser where
12414 happySomeParser = happyThen (happyParse 6#) (\x -> happyReturn (let {(HappyWrap249 x') = happyOut249 x} in x'))
12415
12416parseTypeSignature = happySomeParser where
12417 happySomeParser = happyThen (happyParse 7#) (\x -> happyReturn (let {(HappyWrap205 x') = happyOut205 x} in x'))
12418
12419parseStmt = happySomeParser where
12420 happySomeParser = happyThen (happyParse 8#) (\x -> happyReturn (let {(HappyWrap255 x') = happyOut255 x} in x'))
12421
12422parseIdentifier = happySomeParser where
12423 happySomeParser = happyThen (happyParse 9#) (\x -> happyReturn (let {(HappyWrap16 x') = happyOut16 x} in x'))
12424
12425parseType = happySomeParser where
12426 happySomeParser = happyThen (happyParse 10#) (\x -> happyReturn (let {(HappyWrap155 x') = happyOut155 x} in x'))
12427
12428parseBackpack = happySomeParser where
12429 happySomeParser = happyThen (happyParse 11#) (\x -> happyReturn (let {(HappyWrap17 x') = happyOut17 x} in x'))
12430
12431parseHeader = happySomeParser where
12432 happySomeParser = happyThen (happyParse 12#) (\x -> happyReturn (let {(HappyWrap43 x') = happyOut43 x} in x'))
12433
12434happySeq = happyDoSeq
12435
12436
12437happyError :: P a
12438happyError = srcParseFail
12439
12440getVARID        (dL->L _ (ITvarid    x)) = x
12441getCONID        (dL->L _ (ITconid    x)) = x
12442getVARSYM       (dL->L _ (ITvarsym   x)) = x
12443getCONSYM       (dL->L _ (ITconsym   x)) = x
12444getQVARID       (dL->L _ (ITqvarid   x)) = x
12445getQCONID       (dL->L _ (ITqconid   x)) = x
12446getQVARSYM      (dL->L _ (ITqvarsym  x)) = x
12447getQCONSYM      (dL->L _ (ITqconsym  x)) = x
12448getIPDUPVARID   (dL->L _ (ITdupipvarid   x)) = x
12449getLABELVARID   (dL->L _ (ITlabelvarid   x)) = x
12450getCHAR         (dL->L _ (ITchar   _ x)) = x
12451getSTRING       (dL->L _ (ITstring _ x)) = x
12452getINTEGER      (dL->L _ (ITinteger x))  = x
12453getRATIONAL     (dL->L _ (ITrational x)) = x
12454getPRIMCHAR     (dL->L _ (ITprimchar _ x)) = x
12455getPRIMSTRING   (dL->L _ (ITprimstring _ x)) = x
12456getPRIMINTEGER  (dL->L _ (ITprimint  _ x)) = x
12457getPRIMWORD     (dL->L _ (ITprimword _ x)) = x
12458getPRIMFLOAT    (dL->L _ (ITprimfloat x)) = x
12459getPRIMDOUBLE   (dL->L _ (ITprimdouble x)) = x
12460getTH_ID_SPLICE (dL->L _ (ITidEscape x)) = x
12461getTH_ID_TY_SPLICE (dL->L _ (ITidTyEscape x)) = x
12462getINLINE       (dL->L _ (ITinline_prag _ inl conl)) = (inl,conl)
12463getSPEC_INLINE  (dL->L _ (ITspec_inline_prag _ True))  = (Inline,  FunLike)
12464getSPEC_INLINE  (dL->L _ (ITspec_inline_prag _ False)) = (NoInline,FunLike)
12465getCOMPLETE_PRAGs (dL->L _ (ITcomplete_prag x)) = x
12466
12467getDOCNEXT (dL->L _ (ITdocCommentNext x)) = x
12468getDOCPREV (dL->L _ (ITdocCommentPrev x)) = x
12469getDOCNAMED (dL->L _ (ITdocCommentNamed x)) = x
12470getDOCSECTION (dL->L _ (ITdocSection n x)) = (n, x)
12471
12472getINTEGERs     (dL->L _ (ITinteger (IL src _ _))) = src
12473getCHARs        (dL->L _ (ITchar       src _)) = src
12474getSTRINGs      (dL->L _ (ITstring     src _)) = src
12475getPRIMCHARs    (dL->L _ (ITprimchar   src _)) = src
12476getPRIMSTRINGs  (dL->L _ (ITprimstring src _)) = src
12477getPRIMINTEGERs (dL->L _ (ITprimint    src _)) = src
12478getPRIMWORDs    (dL->L _ (ITprimword   src _)) = src
12479
12480-- See Note [Pragma source text] in BasicTypes for the following
12481getINLINE_PRAGs       (dL->L _ (ITinline_prag       src _ _)) = src
12482getSPEC_PRAGs         (dL->L _ (ITspec_prag         src))     = src
12483getSPEC_INLINE_PRAGs  (dL->L _ (ITspec_inline_prag  src _))   = src
12484getSOURCE_PRAGs       (dL->L _ (ITsource_prag       src)) = src
12485getRULES_PRAGs        (dL->L _ (ITrules_prag        src)) = src
12486getWARNING_PRAGs      (dL->L _ (ITwarning_prag      src)) = src
12487getDEPRECATED_PRAGs   (dL->L _ (ITdeprecated_prag   src)) = src
12488getSCC_PRAGs          (dL->L _ (ITscc_prag          src)) = src
12489getGENERATED_PRAGs    (dL->L _ (ITgenerated_prag    src)) = src
12490getCORE_PRAGs         (dL->L _ (ITcore_prag         src)) = src
12491getUNPACK_PRAGs       (dL->L _ (ITunpack_prag       src)) = src
12492getNOUNPACK_PRAGs     (dL->L _ (ITnounpack_prag     src)) = src
12493getANN_PRAGs          (dL->L _ (ITann_prag          src)) = src
12494getMINIMAL_PRAGs      (dL->L _ (ITminimal_prag      src)) = src
12495getOVERLAPPABLE_PRAGs (dL->L _ (IToverlappable_prag src)) = src
12496getOVERLAPPING_PRAGs  (dL->L _ (IToverlapping_prag  src)) = src
12497getOVERLAPS_PRAGs     (dL->L _ (IToverlaps_prag     src)) = src
12498getINCOHERENT_PRAGs   (dL->L _ (ITincoherent_prag   src)) = src
12499getCTYPEs             (dL->L _ (ITctype             src)) = src
12500
12501getStringLiteral l = StringLiteral (getSTRINGs l) (getSTRING l)
12502
12503isUnicode :: Located Token -> Bool
12504isUnicode (dL->L _ (ITforall         iu)) = iu == UnicodeSyntax
12505isUnicode (dL->L _ (ITdarrow         iu)) = iu == UnicodeSyntax
12506isUnicode (dL->L _ (ITdcolon         iu)) = iu == UnicodeSyntax
12507isUnicode (dL->L _ (ITlarrow         iu)) = iu == UnicodeSyntax
12508isUnicode (dL->L _ (ITrarrow         iu)) = iu == UnicodeSyntax
12509isUnicode (dL->L _ (ITlarrowtail     iu)) = iu == UnicodeSyntax
12510isUnicode (dL->L _ (ITrarrowtail     iu)) = iu == UnicodeSyntax
12511isUnicode (dL->L _ (ITLarrowtail     iu)) = iu == UnicodeSyntax
12512isUnicode (dL->L _ (ITRarrowtail     iu)) = iu == UnicodeSyntax
12513isUnicode (dL->L _ (IToparenbar      iu)) = iu == UnicodeSyntax
12514isUnicode (dL->L _ (ITcparenbar      iu)) = iu == UnicodeSyntax
12515isUnicode (dL->L _ (ITopenExpQuote _ iu)) = iu == UnicodeSyntax
12516isUnicode (dL->L _ (ITcloseQuote     iu)) = iu == UnicodeSyntax
12517isUnicode (dL->L _ (ITstar           iu)) = iu == UnicodeSyntax
12518isUnicode _                           = False
12519
12520hasE :: Located Token -> Bool
12521hasE (dL->L _ (ITopenExpQuote HasE _)) = True
12522hasE (dL->L _ (ITopenTExpQuote HasE))  = True
12523hasE _                             = False
12524
12525getSCC :: Located Token -> P FastString
12526getSCC lt = do let s = getSTRING lt
12527                   err = "Spaces are not allowed in SCCs"
12528               -- We probably actually want to be more restrictive than this
12529               if ' ' `elem` unpackFS s
12530                   then addFatalError (getLoc lt) (text err)
12531                   else return s
12532
12533-- Utilities for combining source spans
12534comb2 :: (HasSrcSpan a , HasSrcSpan b) => a -> b -> SrcSpan
12535comb2 a b = a `seq` b `seq` combineLocs a b
12536
12537comb3 :: (HasSrcSpan a , HasSrcSpan b , HasSrcSpan c) =>
12538         a -> b -> c -> SrcSpan
12539comb3 a b c = a `seq` b `seq` c `seq`
12540    combineSrcSpans (getLoc a) (combineSrcSpans (getLoc b) (getLoc c))
12541
12542comb4 :: (HasSrcSpan a , HasSrcSpan b , HasSrcSpan c , HasSrcSpan d) =>
12543         a -> b -> c -> d -> SrcSpan
12544comb4 a b c d = a `seq` b `seq` c `seq` d `seq`
12545    (combineSrcSpans (getLoc a) $ combineSrcSpans (getLoc b) $
12546                combineSrcSpans (getLoc c) (getLoc d))
12547
12548comb5 :: Located a -> Located b -> Located c -> Located d -> Located e -> SrcSpan
12549comb5 a b c d e = a `seq` b `seq` c `seq` d `seq` e `seq`
12550    (combineSrcSpans (getLoc a) $ combineSrcSpans (getLoc b) $
12551       combineSrcSpans (getLoc c) $ combineSrcSpans (getLoc d) (getLoc e))
12552
12553-- strict constructor version:
12554{-# INLINE sL #-}
12555sL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
12556sL span a = span `seq` a `seq` cL span a
12557
12558-- See Note [Adding location info] for how these utility functions are used
12559
12560-- replaced last 3 CPP macros in this file
12561{-# INLINE sL0 #-}
12562sL0 :: HasSrcSpan a => SrcSpanLess a -> a
12563sL0 = cL noSrcSpan       -- #define L0   L noSrcSpan
12564
12565{-# INLINE sL1 #-}
12566sL1 :: (HasSrcSpan a , HasSrcSpan b) => a -> SrcSpanLess b -> b
12567sL1 x = sL (getLoc x)   -- #define sL1   sL (getLoc $1)
12568
12569{-# INLINE sLL #-}
12570sLL :: (HasSrcSpan a , HasSrcSpan b , HasSrcSpan c) =>
12571       a -> b -> SrcSpanLess c -> c
12572sLL x y = sL (comb2 x y) -- #define LL   sL (comb2 $1 $>)
12573
12574{- Note [Adding location info]
12575   ~~~~~~~~~~~~~~~~~~~~~~~~~~~
12576
12577This is done using the three functions below, sL0, sL1
12578and sLL.  Note that these functions were mechanically
12579converted from the three macros that used to exist before,
12580namely L0, L1 and LL.
12581
12582They each add a SrcSpan to their argument.
12583
12584   sL0  adds 'noSrcSpan', used for empty productions
12585     -- This doesn't seem to work anymore -=chak
12586
12587   sL1  for a production with a single token on the lhs.  Grabs the SrcSpan
12588        from that token.
12589
12590   sLL  for a production with >1 token on the lhs.  Makes up a SrcSpan from
12591        the first and last tokens.
12592
12593These suffice for the majority of cases.  However, we must be
12594especially careful with empty productions: sLL won't work if the first
12595or last token on the lhs can represent an empty span.  In these cases,
12596we have to calculate the span using more of the tokens from the lhs, eg.
12597
12598        | 'newtype' tycl_hdr '=' newconstr deriving
12599                { L (comb3 $1 $4 $5)
12600                    (mkTyData NewType (unLoc $2) $4 (unLoc $5)) }
12601
12602We provide comb3 and comb4 functions which are useful in such cases.
12603
12604Be careful: there's no checking that you actually got this right, the
12605only symptom will be that the SrcSpans of your syntax will be
12606incorrect.
12607
12608-}
12609
12610-- Make a source location for the file.  We're a bit lazy here and just
12611-- make a point SrcSpan at line 1, column 0.  Strictly speaking we should
12612-- try to find the span of the whole file (ToDo).
12613fileSrcSpan :: P SrcSpan
12614fileSrcSpan = do
12615  l <- getRealSrcLoc;
12616  let loc = mkSrcLoc (srcLocFile l) 1 1;
12617  return (mkSrcSpan loc loc)
12618
12619-- Hint about the MultiWayIf extension
12620hintMultiWayIf :: SrcSpan -> P ()
12621hintMultiWayIf span = do
12622  mwiEnabled <- getBit MultiWayIfBit
12623  unless mwiEnabled $ addError span $
12624    text "Multi-way if-expressions need MultiWayIf turned on"
12625
12626-- Hint about explicit-forall
12627hintExplicitForall :: Located Token -> P ()
12628hintExplicitForall tok = do
12629    forall   <- getBit ExplicitForallBit
12630    rulePrag <- getBit InRulePragBit
12631    unless (forall || rulePrag) $ addError (getLoc tok) $ vcat
12632      [ text "Illegal symbol" <+> quotes forallSymDoc <+> text "in type"
12633      , text "Perhaps you intended to use RankNTypes or a similar language"
12634      , text "extension to enable explicit-forall syntax:" <+>
12635        forallSymDoc <+> text "<tvs>. <type>"
12636      ]
12637  where
12638    forallSymDoc = text (forallSym (isUnicode tok))
12639
12640-- When two single quotes don't followed by tyvar or gtycon, we report the
12641-- error as empty character literal, or TH quote that missing proper type
12642-- variable or constructor. See #13450.
12643reportEmptyDoubleQuotes :: SrcSpan -> P a
12644reportEmptyDoubleQuotes span = do
12645    thQuotes <- getBit ThQuotesBit
12646    if thQuotes
12647      then addFatalError span $ vcat
12648        [ text "Parser error on `''`"
12649        , text "Character literals may not be empty"
12650        , text "Or perhaps you intended to use quotation syntax of TemplateHaskell,"
12651        , text "but the type variable or constructor is missing"
12652        ]
12653      else addFatalError span $ vcat
12654        [ text "Parser error on `''`"
12655        , text "Character literals may not be empty"
12656        ]
12657
12658{-
12659%************************************************************************
12660%*                                                                      *
12661        Helper functions for generating annotations in the parser
12662%*                                                                      *
12663%************************************************************************
12664
12665For the general principles of the following routines, see Note [Api annotations]
12666in ApiAnnotation.hs
12667
12668-}
12669
12670-- |Construct an AddAnn from the annotation keyword and the location
12671-- of the keyword itself
12672mj :: HasSrcSpan e => AnnKeywordId -> e -> AddAnn
12673mj a l = AddAnn a (gl l)
12674
12675mjL :: AnnKeywordId -> SrcSpan -> AddAnn
12676mjL = AddAnn
12677
12678
12679
12680-- |Construct an AddAnn from the annotation keyword and the Located Token. If
12681-- the token has a unicode equivalent and this has been used, provide the
12682-- unicode variant of the annotation.
12683mu :: AnnKeywordId -> Located Token -> AddAnn
12684mu a lt@(dL->L l t) = AddAnn (toUnicodeAnn a lt) l
12685
12686-- | If the 'Token' is using its unicode variant return the unicode variant of
12687--   the annotation
12688toUnicodeAnn :: AnnKeywordId -> Located Token -> AnnKeywordId
12689toUnicodeAnn a t = if isUnicode t then unicodeAnn a else a
12690
12691gl :: HasSrcSpan a => a -> SrcSpan
12692gl = getLoc
12693
12694-- |Add an annotation to the located element, and return the located
12695-- element as a pass through
12696aa :: (HasSrcSpan a , HasSrcSpan c) => a -> (AnnKeywordId, c) -> P a
12697aa a@(dL->L l _) (b,s) = addAnnotation l b (gl s) >> return a
12698
12699-- |Add an annotation to a located element resulting from a monadic action
12700am :: (HasSrcSpan a , HasSrcSpan b) => P a -> (AnnKeywordId, b) -> P a
12701am a (b,s) = do
12702  av@(dL->L l _) <- a
12703  addAnnotation l b (gl s)
12704  return av
12705
12706-- | Add a list of AddAnns to the given AST element.  For example,
12707-- the parsing rule for @let@ looks like:
12708--
12709-- @
12710--      | 'let' binds 'in' exp    {% ams (sLL $1 $> $ HsLet (snd $ unLoc $2) $4)
12711--                                       (mj AnnLet $1:mj AnnIn $3
12712--                                         :(fst $ unLoc $2)) }
12713-- @
12714--
12715-- This adds an AnnLet annotation for @let@, an AnnIn for @in@, as well
12716-- as any annotations that may arise in the binds. This will include open
12717-- and closing braces if they are used to delimit the let expressions.
12718--
12719ams :: (MonadP m, HasSrcSpan a) => a -> [AddAnn] -> m a
12720ams a@(dL->L l _) bs = addAnnsAt l bs >> return a
12721
12722amsL :: SrcSpan -> [AddAnn] -> P ()
12723amsL sp bs = addAnnsAt sp bs >> return ()
12724
12725-- |Add all [AddAnn] to an AST element, and wrap it in a 'Just'
12726ajs :: (MonadP m, HasSrcSpan a) => a -> [AddAnn] -> m (Maybe a)
12727ajs a bs = Just <$> ams a bs
12728
12729-- |Add a list of AddAnns to the given AST element, where the AST element is the
12730--  result of a monadic action
12731amms :: MonadP m => HasSrcSpan a => m a -> [AddAnn] -> m a
12732amms a bs = do { av@(dL->L l _) <- a
12733               ; addAnnsAt l bs
12734               ; return av }
12735
12736-- |Add a list of AddAnns to the AST element, and return the element as a
12737--  OrdList
12738amsu :: HasSrcSpan a => a -> [AddAnn] -> P (OrdList a)
12739amsu a@(dL->L l _) bs = addAnnsAt l bs >> return (unitOL a)
12740
12741-- |Synonyms for AddAnn versions of AnnOpen and AnnClose
12742mo,mc :: Located Token -> AddAnn
12743mo ll = mj AnnOpen ll
12744mc ll = mj AnnClose ll
12745
12746moc,mcc :: Located Token -> AddAnn
12747moc ll = mj AnnOpenC ll
12748mcc ll = mj AnnCloseC ll
12749
12750mop,mcp :: Located Token -> AddAnn
12751mop ll = mj AnnOpenP ll
12752mcp ll = mj AnnCloseP ll
12753
12754mos,mcs :: Located Token -> AddAnn
12755mos ll = mj AnnOpenS ll
12756mcs ll = mj AnnCloseS ll
12757
12758-- |Given a list of the locations of commas, provide a [AddAnn] with an AnnComma
12759--  entry for each SrcSpan
12760mcommas :: [SrcSpan] -> [AddAnn]
12761mcommas ss = map (mjL AnnCommaTuple) ss
12762
12763-- |Given a list of the locations of '|'s, provide a [AddAnn] with an AnnVbar
12764--  entry for each SrcSpan
12765mvbars :: [SrcSpan] -> [AddAnn]
12766mvbars ss = map (mjL AnnVbar) ss
12767
12768-- |Get the location of the last element of a OrdList, or noSrcSpan
12769oll :: HasSrcSpan a => OrdList a -> SrcSpan
12770oll l =
12771  if isNilOL l then noSrcSpan
12772               else getLoc (lastOL l)
12773
12774-- |Add a semicolon annotation in the right place in a list. If the
12775-- leading list is empty, add it to the tail
12776asl :: (HasSrcSpan a , HasSrcSpan b) => [a] -> b -> a -> P()
12777asl [] (dL->L ls _) (dL->L l _) = addAnnotation l          AnnSemi ls
12778asl (x:_xs) (dL->L ls _) _x = addAnnotation (getLoc x) AnnSemi ls
12779{-# LINE 1 "templates/GenericTemplate.hs" #-}
12780-- $Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp $
12781
12782
12783
12784
12785
12786
12787
12788
12789
12790
12791
12792
12793
12794-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
12795#if __GLASGOW_HASKELL__ > 706
12796#define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Bool)
12797#define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Bool)
12798#define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Bool)
12799#else
12800#define LT(n,m) (n Happy_GHC_Exts.<# m)
12801#define GTE(n,m) (n Happy_GHC_Exts.>=# m)
12802#define EQ(n,m) (n Happy_GHC_Exts.==# m)
12803#endif
12804
12805
12806
12807
12808
12809
12810
12811
12812
12813
12814
12815
12816
12817
12818
12819
12820
12821
12822
12823data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList
12824
12825
12826
12827
12828
12829
12830
12831
12832
12833
12834
12835
12836
12837
12838
12839
12840
12841
12842
12843
12844
12845
12846
12847
12848
12849
12850
12851
12852
12853
12854
12855
12856
12857
12858
12859
12860
12861
12862
12863
12864infixr 9 `HappyStk`
12865data HappyStk a = HappyStk a (HappyStk a)
12866
12867-----------------------------------------------------------------------------
12868-- starting the parse
12869
12870happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll
12871
12872-----------------------------------------------------------------------------
12873-- Accepting the parse
12874
12875-- If the current token is ERROR_TOK, it means we've just accepted a partial
12876-- parse (a %partial parser).  We must ignore the saved token on the top of
12877-- the stack in this case.
12878happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
12879        happyReturn1 ans
12880happyAccept j tk st sts (HappyStk ans _) =
12881        (happyTcHack j (happyTcHack st)) (happyReturn1 ans)
12882
12883-----------------------------------------------------------------------------
12884-- Arrays only: do the next action
12885
12886
12887
12888happyDoAction i tk st
12889        = {- nothing -}
12890          case action of
12891                0#           -> {- nothing -}
12892                                     happyFail (happyExpListPerState ((Happy_GHC_Exts.I# (st)) :: Int)) i tk st
12893                -1#          -> {- nothing -}
12894                                     happyAccept i tk st
12895                n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}
12896                                                   (happyReduceArr Happy_Data_Array.! rule) i tk st
12897                                                   where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
12898                n                 -> {- nothing -}
12899                                     happyShift new_state i tk st
12900                                     where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
12901   where off    = happyAdjustOffset (indexShortOffAddr happyActOffsets st)
12902         off_i  = (off Happy_GHC_Exts.+# i)
12903         check  = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#))
12904                  then EQ(indexShortOffAddr happyCheck off_i, i)
12905                  else False
12906         action
12907          | check     = indexShortOffAddr happyTable off_i
12908          | otherwise = indexShortOffAddr happyDefActions st
12909
12910
12911
12912
12913indexShortOffAddr (HappyA# arr) off =
12914        Happy_GHC_Exts.narrow16Int# i
12915  where
12916        i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low)
12917        high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#)))
12918        low  = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off'))
12919        off' = off Happy_GHC_Exts.*# 2#
12920
12921
12922
12923
12924{-# INLINE happyLt #-}
12925happyLt x y = LT(x,y)
12926
12927
12928readArrayBit arr bit =
12929    Bits.testBit (Happy_GHC_Exts.I# (indexShortOffAddr arr ((unbox_int bit) `Happy_GHC_Exts.iShiftRA#` 4#))) (bit `mod` 16)
12930  where unbox_int (Happy_GHC_Exts.I# x) = x
12931
12932
12933
12934
12935
12936
12937data HappyAddr = HappyA# Happy_GHC_Exts.Addr#
12938
12939
12940-----------------------------------------------------------------------------
12941-- HappyState data type (not arrays)
12942
12943
12944
12945
12946
12947
12948
12949
12950
12951
12952
12953
12954
12955-----------------------------------------------------------------------------
12956-- Shifting a token
12957
12958happyShift new_state 0# tk st sts stk@(x `HappyStk` _) =
12959     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
12960--     trace "shifting the error token" $
12961     happyDoAction i tk new_state (HappyCons (st) (sts)) (stk)
12962
12963happyShift new_state i tk st sts stk =
12964     happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk)
12965
12966-- happyReduce is specialised for the common cases.
12967
12968happySpecReduce_0 i fn 0# tk st sts stk
12969     = happyFail [] 0# tk st sts stk
12970happySpecReduce_0 nt fn j tk st@((action)) sts stk
12971     = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk)
12972
12973happySpecReduce_1 i fn 0# tk st sts stk
12974     = happyFail [] 0# tk st sts stk
12975happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk')
12976     = let r = fn v1 in
12977       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
12978
12979happySpecReduce_2 i fn 0# tk st sts stk
12980     = happyFail [] 0# tk st sts stk
12981happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk')
12982     = let r = fn v1 v2 in
12983       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
12984
12985happySpecReduce_3 i fn 0# tk st sts stk
12986     = happyFail [] 0# tk st sts stk
12987happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
12988     = let r = fn v1 v2 v3 in
12989       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
12990
12991happyReduce k i fn 0# tk st sts stk
12992     = happyFail [] 0# tk st sts stk
12993happyReduce k nt fn j tk st sts stk
12994     = case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of
12995         sts1@((HappyCons (st1@(action)) (_))) ->
12996                let r = fn stk in  -- it doesn't hurt to always seq here...
12997                happyDoSeq r (happyGoto nt j tk st1 sts1 r)
12998
12999happyMonadReduce k nt fn 0# tk st sts stk
13000     = happyFail [] 0# tk st sts stk
13001happyMonadReduce k nt fn j tk st sts stk =
13002      case happyDrop k (HappyCons (st) (sts)) of
13003        sts1@((HappyCons (st1@(action)) (_))) ->
13004          let drop_stk = happyDropStk k stk in
13005          happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))
13006
13007happyMonad2Reduce k nt fn 0# tk st sts stk
13008     = happyFail [] 0# tk st sts stk
13009happyMonad2Reduce k nt fn j tk st sts stk =
13010      case happyDrop k (HappyCons (st) (sts)) of
13011        sts1@((HappyCons (st1@(action)) (_))) ->
13012         let drop_stk = happyDropStk k stk
13013
13014             off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st1)
13015             off_i = (off Happy_GHC_Exts.+# nt)
13016             new_state = indexShortOffAddr happyTable off_i
13017
13018
13019
13020
13021          in
13022          happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))
13023
13024happyDrop 0# l = l
13025happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t
13026
13027happyDropStk 0# l = l
13028happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs
13029
13030-----------------------------------------------------------------------------
13031-- Moving to a new state after a reduction
13032
13033
13034happyGoto nt j tk st =
13035   {- nothing -}
13036   happyDoAction j tk new_state
13037   where off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st)
13038         off_i = (off Happy_GHC_Exts.+# nt)
13039         new_state = indexShortOffAddr happyTable off_i
13040
13041
13042
13043
13044-----------------------------------------------------------------------------
13045-- Error recovery (ERROR_TOK is the error token)
13046
13047-- parse error if we are in recovery and we fail again
13048happyFail explist 0# tk old_st _ stk@(x `HappyStk` _) =
13049     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
13050--      trace "failing" $
13051        happyError_ explist i tk
13052
13053{-  We don't need state discarding for our restricted implementation of
13054    "error".  In fact, it can cause some bogus parses, so I've disabled it
13055    for now --SDM
13056
13057-- discard a state
13058happyFail  ERROR_TOK tk old_st CONS(HAPPYSTATE(action),sts)
13059                                                (saved_tok `HappyStk` _ `HappyStk` stk) =
13060--      trace ("discarding state, depth " ++ show (length stk))  $
13061        DO_ACTION(action,ERROR_TOK,tk,sts,(saved_tok`HappyStk`stk))
13062-}
13063
13064-- Enter error recovery: generate an error token,
13065--                       save the old token and carry on.
13066happyFail explist i tk (action) sts stk =
13067--      trace "entering error recovery" $
13068        happyDoAction 0# tk action sts ((Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk)
13069
13070-- Internal happy errors:
13071
13072notHappyAtAll :: a
13073notHappyAtAll = error "Internal Happy error\n"
13074
13075-----------------------------------------------------------------------------
13076-- Hack to get the typechecker to accept our action functions
13077
13078
13079happyTcHack :: Happy_GHC_Exts.Int# -> a -> a
13080happyTcHack x y = y
13081{-# INLINE happyTcHack #-}
13082
13083
13084-----------------------------------------------------------------------------
13085-- Seq-ing.  If the --strict flag is given, then Happy emits
13086--      happySeq = happyDoSeq
13087-- otherwise it emits
13088--      happySeq = happyDontSeq
13089
13090happyDoSeq, happyDontSeq :: a -> b -> b
13091happyDoSeq   a b = a `seq` b
13092happyDontSeq a b = b
13093
13094-----------------------------------------------------------------------------
13095-- Don't inline any functions from the template.  GHC has a nasty habit
13096-- of deciding to inline happyGoto everywhere, which increases the size of
13097-- the generated parser quite a bit.
13098
13099
13100{-# NOINLINE happyDoAction #-}
13101{-# NOINLINE happyTable #-}
13102{-# NOINLINE happyCheck #-}
13103{-# NOINLINE happyActOffsets #-}
13104{-# NOINLINE happyGotoOffsets #-}
13105{-# NOINLINE happyDefActions #-}
13106
13107{-# NOINLINE happyShift #-}
13108{-# NOINLINE happySpecReduce_0 #-}
13109{-# NOINLINE happySpecReduce_1 #-}
13110{-# NOINLINE happySpecReduce_2 #-}
13111{-# NOINLINE happySpecReduce_3 #-}
13112{-# NOINLINE happyReduce #-}
13113{-# NOINLINE happyMonadReduce #-}
13114{-# NOINLINE happyGoto #-}
13115{-# NOINLINE happyFail #-}
13116
13117-- end of Happy Template.
13118