{-# OPTIONS_GHC -w #-} {-# OPTIONS_GHC -fno-warn-incomplete-patterns -fno-warn-overlapping-patterns #-} module ParBNF where import qualified AbsBNF import LexBNF import qualified Data.Array as Happy_Data_Array import qualified Data.Bits as Bits import Control.Applicative(Applicative(..)) import Control.Monad (ap) -- parser produced by Happy Version 1.20.0 data HappyAbsSyn = HappyTerminal (Token) | HappyErrorToken Prelude.Int | HappyAbsSyn36 (String) | HappyAbsSyn37 (Integer) | HappyAbsSyn38 (Char) | HappyAbsSyn39 (Double) | HappyAbsSyn40 (AbsBNF.Identifier) | HappyAbsSyn41 (AbsBNF.LGrammar) | HappyAbsSyn42 (AbsBNF.LDef) | HappyAbsSyn43 ([AbsBNF.LDef]) | HappyAbsSyn44 ([AbsBNF.Identifier]) | HappyAbsSyn45 (AbsBNF.Grammar) | HappyAbsSyn46 ([AbsBNF.Def]) | HappyAbsSyn47 (AbsBNF.Def) | HappyAbsSyn48 (AbsBNF.Item) | HappyAbsSyn49 ([AbsBNF.Item]) | HappyAbsSyn50 (AbsBNF.Cat) | HappyAbsSyn51 (AbsBNF.Label) | HappyAbsSyn52 (AbsBNF.LabelId) | HappyAbsSyn53 (AbsBNF.ProfItem) | HappyAbsSyn54 (AbsBNF.IntList) | HappyAbsSyn55 ([Integer]) | HappyAbsSyn56 ([AbsBNF.IntList]) | HappyAbsSyn57 ([AbsBNF.ProfItem]) | HappyAbsSyn58 (AbsBNF.Arg) | HappyAbsSyn59 ([AbsBNF.Arg]) | HappyAbsSyn60 (AbsBNF.Separation) | HappyAbsSyn61 ([String]) | HappyAbsSyn62 (AbsBNF.Exp) | HappyAbsSyn65 ([AbsBNF.Exp]) | HappyAbsSyn67 (AbsBNF.RHS) | HappyAbsSyn68 ([AbsBNF.RHS]) | HappyAbsSyn69 (AbsBNF.MinimumSize) | HappyAbsSyn70 (AbsBNF.Reg) {- to allow type-synonyms as our monads (likely - with explicitly-specified bind and return) - in Haskell98, it seems that with - /type M a = .../, then /(HappyReduction M)/ - is not allowed. But Happy is a - code-generator that can just substitute it. type HappyReduction m = Prelude.Int -> (Token) -> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> m HappyAbsSyn) -> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> m HappyAbsSyn)] -> HappyStk HappyAbsSyn -> [(Token)] -> m HappyAbsSyn -} action_0, action_1, action_2, action_3, action_4, action_5, action_6, action_7, action_8, action_9, action_10, action_11, action_12, action_13, action_14, action_15, action_16, action_17, action_18, action_19, action_20, action_21, action_22, action_23, action_24, action_25, action_26, action_27, action_28, action_29, action_30, action_31, action_32, action_33, action_34, action_35, action_36, action_37, action_38, action_39, action_40, action_41, action_42, action_43, action_44, action_45, action_46, action_47, action_48, action_49, action_50, action_51, action_52, action_53, action_54, action_55, action_56, action_57, action_58, action_59, action_60, action_61, action_62, action_63, action_64, action_65, action_66, action_67, action_68, action_69, action_70, action_71, action_72, action_73, action_74, action_75, action_76, action_77, action_78, action_79, action_80, action_81, action_82, action_83, action_84, action_85, action_86, action_87, action_88, action_89, action_90, action_91, action_92, action_93, action_94, action_95, action_96, action_97, action_98, action_99, action_100, action_101, action_102, action_103, action_104, action_105, action_106, action_107, action_108, action_109, action_110, action_111, action_112, action_113, action_114, action_115, action_116, action_117, action_118, action_119, action_120, action_121, action_122, action_123, action_124, action_125, action_126, action_127, action_128, action_129, action_130, action_131, action_132, action_133, action_134, action_135, action_136, action_137, action_138, action_139, action_140, action_141, action_142, action_143, action_144, action_145, action_146, action_147, action_148, action_149, action_150, action_151, action_152, action_153, action_154, action_155, action_156, action_157, action_158, action_159, action_160, action_161, action_162, action_163, action_164, action_165, action_166, action_167, action_168, action_169, action_170, action_171, action_172, action_173, action_174, action_175, action_176, action_177, action_178, action_179, action_180, action_181, action_182, action_183, action_184, action_185, action_186, action_187, action_188, action_189, action_190, action_191, action_192, action_193, action_194, action_195, action_196, action_197, action_198, action_199, action_200, action_201, action_202, action_203, action_204, action_205, action_206, action_207, action_208, action_209, action_210, action_211, action_212, action_213, action_214, action_215, action_216, action_217, action_218, action_219, action_220, action_221, action_222, action_223, action_224, action_225, action_226, action_227, action_228, action_229, action_230, action_231, action_232, action_233, action_234, action_235, action_236, action_237, action_238, action_239, action_240, action_241, action_242, action_243, action_244, action_245, action_246, action_247, action_248, action_249, action_250, action_251, action_252, action_253, action_254 :: () => Prelude.Int -> ({-HappyReduction (Either String) = -} Prelude.Int -> (Token) -> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn) -> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn)] -> HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn) happyReduce_33, happyReduce_34, happyReduce_35, happyReduce_36, happyReduce_37, happyReduce_38, happyReduce_39, happyReduce_40, happyReduce_41, happyReduce_42, happyReduce_43, happyReduce_44, happyReduce_45, happyReduce_46, happyReduce_47, happyReduce_48, happyReduce_49, happyReduce_50, happyReduce_51, happyReduce_52, happyReduce_53, happyReduce_54, happyReduce_55, happyReduce_56, happyReduce_57, happyReduce_58, happyReduce_59, happyReduce_60, happyReduce_61, happyReduce_62, happyReduce_63, happyReduce_64, happyReduce_65, happyReduce_66, happyReduce_67, happyReduce_68, happyReduce_69, happyReduce_70, happyReduce_71, happyReduce_72, happyReduce_73, happyReduce_74, happyReduce_75, happyReduce_76, happyReduce_77, happyReduce_78, happyReduce_79, happyReduce_80, happyReduce_81, happyReduce_82, happyReduce_83, happyReduce_84, happyReduce_85, happyReduce_86, happyReduce_87, happyReduce_88, happyReduce_89, happyReduce_90, happyReduce_91, happyReduce_92, happyReduce_93, happyReduce_94, happyReduce_95, happyReduce_96, happyReduce_97, happyReduce_98, happyReduce_99, happyReduce_100, happyReduce_101, happyReduce_102, happyReduce_103, happyReduce_104, happyReduce_105, happyReduce_106, happyReduce_107, happyReduce_108, happyReduce_109, happyReduce_110, happyReduce_111, happyReduce_112, happyReduce_113, happyReduce_114, happyReduce_115, happyReduce_116, happyReduce_117, happyReduce_118, happyReduce_119, happyReduce_120, happyReduce_121, happyReduce_122, happyReduce_123, happyReduce_124, happyReduce_125, happyReduce_126, happyReduce_127, happyReduce_128, happyReduce_129, happyReduce_130, happyReduce_131, happyReduce_132, happyReduce_133, happyReduce_134, happyReduce_135, happyReduce_136, happyReduce_137, happyReduce_138, happyReduce_139, happyReduce_140, happyReduce_141 :: () => ({-HappyReduction (Either String) = -} Prelude.Int -> (Token) -> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn) -> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn)] -> HappyStk HappyAbsSyn -> [(Token)] -> (Either String) HappyAbsSyn) happyExpList :: Happy_Data_Array.Array Prelude.Int Prelude.Int happyExpList = Happy_Data_Array.listArray (0,638) ([0,0,0,0,512,24228,9955,32,0,0,0,0,20481,29103,4115,0,0,0,0,128,55209,2488,8,0,0,0,0,0,0,1024,0,0,0,0,16416,13802,110,2,0,0,0,4096,62752,14106,256,0,0,0,0,32776,36218,32795,0,0,0,0,0,64,0,68,0,0,0,0,8192,0,8704,0,0,0,0,0,16,0,16,0,0,0,32768,10240,0,2048,0,0,0,0,64,20,0,4,0,0,0,8192,0,0,0,0,0,0,0,0,1,0,0,0,0,0,0,0,0,16,0,0,0,0,16384,0,0,0,0,0,0,512,0,0,0,0,0,0,0,0,0,4096,0,0,0,0,0,0,0,8,0,0,0,0,0,20480,0,0,0,0,0,0,0,8192,0,0,0,0,4096,256,0,496,0,0,0,0,32776,0,63488,0,0,0,0,1024,64,0,124,0,0,0,0,8194,0,15872,0,0,0,0,256,16,0,31,0,0,0,0,2048,0,2176,0,0,0,0,0,4,16384,4,0,0,0,0,0,256,0,0,0,0,0,16,25865,17024,0,0,0,0,2048,33920,16434,33,0,0,0,0,16388,6466,4256,0,0,0,0,512,41248,20492,8,0,0,0,0,0,0,256,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,384,1,0,0,0,0,0,4096,2304,32869,66,0,0,0,0,0,0,2048,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,4096,0,0,0,0,0,0,0,0,0,0,0,0,16388,6466,4256,0,0,0,0,6144,16,0,0,0,0,0,0,32,0,0,0,0,0,0,128,10312,5123,2,0,0,0,0,0,0,16,0,0,0,0,1024,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,0,17,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8,0,0,0,0,0,0,0,0,0,0,0,0,128,0,128,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32776,0,63488,0,0,0,0,0,0,0,0,0,0,0,0,8194,0,15872,0,0,0,0,256,16,0,31,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8192,512,0,992,0,0,0,0,256,0,0,0,0,0,0,0,4,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,512,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,4,0,0,0,0,0,0,512,0,0,0,0,0,0,0,0,0,0,0,0,0,0,2048,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16384,0,0,0,0,0,0,8192,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0,0,0,0,4,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32768,0,0,0,0,0,0,0,4096,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,5,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8192,0,0,0,0,0,0,0,0,0,1024,0,0,0,0,0,0,8192,0,0,0,0,0,0,0,256,0,0,0,0,32768,0,32768,0,0,0,0,0,0,0,64,0,0,0,0,40962,0,8192,0,0,0,0,0,0,1152,1,0,0,0,0,0,0,1,0,0,0,0,0,0,0,4,0,0,0,0,0,256,0,0,0,0,0,0,32768,0,0,0,0,0,0,0,0,128,0,0,0,0,0,0,0,0,0,0,0,0,4,0,0,0,0,0,0,20993,29103,4099,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,512,0,0,0,0,0,0,0,0,0,0,0,0,0,0,128,0,0,0,0,0,0,0,8,0,0,0,0,0,0,0,0,0,0,0,0,0,32768,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32832,27604,1244,4,0,0,0,0,0,0,512,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,128,55208,440,8,0,0,0,16384,54400,56427,1028,0,0,0,0,0,0,0,2,0,0,0,0,0,0,0,0,0,0,0,36872,36218,32795,0,0,0,0,1024,16960,40985,16,0,0,0,0,8192,0,8192,0,0,0,0,0,16,0,16,0,0,0,0,128,0,0,0,0,0,0,0,0,0,4,0,0,0,0,0,0,0,0,0,0,0,0,0,4096,0,0,0,0,0,0,0,0,0,0,0,0,256,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,256,0,0,0,0,0,0,0,8,0,0,0,0,0,0,64,0,0,0,0,0,0,16384,0,0,0,0,0,256,0,256,0,0,0,0,8,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8448,0,0,0,0,0,0,0,0,0,0,0,0,0,0,2049,0,0,0,0,0,0,0,0,32768,0,0,0,0,0,1024,0,0,0,0,0,0,0,1,0,0,0,0,0,0,128,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,64,0,0,0,0,32,2,57344,3,0,0,0,4096,256,0,496,0,0,0,0,0,0,0,0,0,0,0,0,128,0,0,0,0,0,0,4,0,0,0,0,0,0,0,0,0,0,0,0,0,0,4096,0,0,0,0,0,0,0,4,16384,4,0,0,0,0,0,0,0,0,0,0,0,16,25865,17024,0,0,0,0,2048,33920,16434,33,0,0,0,0,8240,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32,0,0,0,0,0,4,0,0,0,0,0,8192,0,0,4,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8192,0,0,0,0,0,0,32768,18432,808,532,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,128,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,128,0,0,0,0,0,0,0,0,4096,0,0,0,0,0,128,0,128,0,0,0,0,0,0,0,0,0,0,0,512,41248,20492,8,0,0,0,0,4096,0,4352,0,0,0,0,0,0,32768,0,0,0,0,0,0,0,64,0,0,0,0,0,0,2048,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,8,0,0,0,0,4096,0,0,0,0,0,0,0,0,2560,0,0,0,0,0,16388,0,31744,0,0,0,0,0,32,0,34,0,0,0,0,2,0,0,0,0,0,0,2048,0,0,0,0,0,0,0,1024,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32,0,0,0,0,0,8192,0,8704,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,32768,0,0,0,0,0,1024,0,0,0,0,0,0,32,0,0,0,0,0,0,0,0,0,0,0 ]) {-# NOINLINE happyExpListPerState #-} happyExpListPerState st = token_strs_expected where token_strs = ["error","%dummy","%start_pLGrammar","%start_pLDef","%start_pListLDef","%start_pListIdentifier","%start_pGrammar","%start_pListDef","%start_pDef","%start_pItem","%start_pListItem","%start_pCat","%start_pLabel","%start_pLabelId","%start_pProfItem","%start_pIntList","%start_pListInteger","%start_pListIntList","%start_pListProfItem","%start_pArg","%start_pListArg","%start_pSeparation","%start_pListString","%start_pExp","%start_pExp1","%start_pExp2","%start_pListExp","%start_pListExp2","%start_pRHS","%start_pListRHS","%start_pMinimumSize","%start_pReg","%start_pReg1","%start_pReg2","%start_pReg3","String","Integer","Char","Double","Identifier","LGrammar","LDef","ListLDef","ListIdentifier","Grammar","ListDef","Def","Item","ListItem","Cat","Label","LabelId","ProfItem","IntList","ListInteger","ListIntList","ListProfItem","Arg","ListArg","Separation","ListString","Exp","Exp1","Exp2","ListExp","ListExp2","RHS","ListRHS","MinimumSize","Reg","Reg1","Reg2","Reg3","'('","')'","'*'","'+'","','","'-'","'.'","':'","'::='","';'","'='","'?'","'['","']'","'_'","'char'","'coercions'","'comment'","'define'","'delimiters'","'digit'","'entrypoints'","'eps'","'internal'","'layout'","'letter'","'lower'","'nonempty'","'position'","'rules'","'separator'","'stop'","'terminator'","'token'","'toplevel'","'upper'","'views'","'{'","'|'","'}'","L_quoted","L_integ","L_charac","L_doubl","L_Identifier","%eof"] bit_start = st Prelude.* 119 bit_end = (st Prelude.+ 1) Prelude.* 119 read_bit = readArrayBit happyExpList bits = Prelude.map read_bit [bit_start..bit_end Prelude.- 1] bits_indexed = Prelude.zip bits [0..118] token_strs_expected = Prelude.concatMap f bits_indexed f (Prelude.False, _) = [] f (Prelude.True, nr) = [token_strs Prelude.!! nr] action_0 (74) = happyShift action_105 action_0 (83) = happyShift action_139 action_0 (86) = happyShift action_106 action_0 (88) = happyShift action_107 action_0 (90) = happyShift action_115 action_0 (91) = happyShift action_116 action_0 (92) = happyShift action_117 action_0 (93) = happyShift action_118 action_0 (95) = happyShift action_119 action_0 (97) = happyShift action_120 action_0 (98) = happyShift action_121 action_0 (102) = happyShift action_122 action_0 (103) = happyShift action_123 action_0 (104) = happyShift action_124 action_0 (106) = happyShift action_125 action_0 (107) = happyShift action_126 action_0 (110) = happyShift action_140 action_0 (118) = happyShift action_63 action_0 (40) = happyGoto action_134 action_0 (41) = happyGoto action_142 action_0 (42) = happyGoto action_135 action_0 (43) = happyGoto action_143 action_0 (44) = happyGoto action_137 action_0 (47) = happyGoto action_138 action_0 (51) = happyGoto action_114 action_0 (52) = happyGoto action_109 action_0 _ = happyReduce_42 action_1 (74) = happyShift action_105 action_1 (86) = happyShift action_106 action_1 (88) = happyShift action_107 action_1 (90) = happyShift action_115 action_1 (91) = happyShift action_116 action_1 (92) = happyShift action_117 action_1 (93) = happyShift action_118 action_1 (95) = happyShift action_119 action_1 (97) = happyShift action_120 action_1 (98) = happyShift action_121 action_1 (102) = happyShift action_122 action_1 (103) = happyShift action_123 action_1 (104) = happyShift action_124 action_1 (106) = happyShift action_125 action_1 (107) = happyShift action_126 action_1 (110) = happyShift action_140 action_1 (118) = happyShift action_63 action_1 (40) = happyGoto action_134 action_1 (42) = happyGoto action_141 action_1 (44) = happyGoto action_137 action_1 (47) = happyGoto action_138 action_1 (51) = happyGoto action_114 action_1 (52) = happyGoto action_109 action_1 _ = happyFail (happyExpListPerState 1) action_2 (74) = happyShift action_105 action_2 (83) = happyShift action_139 action_2 (86) = happyShift action_106 action_2 (88) = happyShift action_107 action_2 (90) = happyShift action_115 action_2 (91) = happyShift action_116 action_2 (92) = happyShift action_117 action_2 (93) = happyShift action_118 action_2 (95) = happyShift action_119 action_2 (97) = happyShift action_120 action_2 (98) = happyShift action_121 action_2 (102) = happyShift action_122 action_2 (103) = happyShift action_123 action_2 (104) = happyShift action_124 action_2 (106) = happyShift action_125 action_2 (107) = happyShift action_126 action_2 (110) = happyShift action_140 action_2 (118) = happyShift action_63 action_2 (40) = happyGoto action_134 action_2 (42) = happyGoto action_135 action_2 (43) = happyGoto action_136 action_2 (44) = happyGoto action_137 action_2 (47) = happyGoto action_138 action_2 (51) = happyGoto action_114 action_2 (52) = happyGoto action_109 action_2 _ = happyReduce_42 action_3 (118) = happyShift action_63 action_3 (40) = happyGoto action_132 action_3 (44) = happyGoto action_133 action_3 _ = happyFail (happyExpListPerState 3) action_4 (74) = happyShift action_105 action_4 (83) = happyShift action_129 action_4 (86) = happyShift action_106 action_4 (88) = happyShift action_107 action_4 (90) = happyShift action_115 action_4 (91) = happyShift action_116 action_4 (92) = happyShift action_117 action_4 (93) = happyShift action_118 action_4 (95) = happyShift action_119 action_4 (97) = happyShift action_120 action_4 (98) = happyShift action_121 action_4 (102) = happyShift action_122 action_4 (103) = happyShift action_123 action_4 (104) = happyShift action_124 action_4 (106) = happyShift action_125 action_4 (107) = happyShift action_126 action_4 (118) = happyShift action_63 action_4 (40) = happyGoto action_103 action_4 (45) = happyGoto action_130 action_4 (46) = happyGoto action_131 action_4 (47) = happyGoto action_128 action_4 (51) = happyGoto action_114 action_4 (52) = happyGoto action_109 action_4 _ = happyReduce_49 action_5 (74) = happyShift action_105 action_5 (83) = happyShift action_129 action_5 (86) = happyShift action_106 action_5 (88) = happyShift action_107 action_5 (90) = happyShift action_115 action_5 (91) = happyShift action_116 action_5 (92) = happyShift action_117 action_5 (93) = happyShift action_118 action_5 (95) = happyShift action_119 action_5 (97) = happyShift action_120 action_5 (98) = happyShift action_121 action_5 (102) = happyShift action_122 action_5 (103) = happyShift action_123 action_5 (104) = happyShift action_124 action_5 (106) = happyShift action_125 action_5 (107) = happyShift action_126 action_5 (118) = happyShift action_63 action_5 (40) = happyGoto action_103 action_5 (46) = happyGoto action_127 action_5 (47) = happyGoto action_128 action_5 (51) = happyGoto action_114 action_5 (52) = happyGoto action_109 action_5 _ = happyReduce_49 action_6 (74) = happyShift action_105 action_6 (86) = happyShift action_106 action_6 (88) = happyShift action_107 action_6 (90) = happyShift action_115 action_6 (91) = happyShift action_116 action_6 (92) = happyShift action_117 action_6 (93) = happyShift action_118 action_6 (95) = happyShift action_119 action_6 (97) = happyShift action_120 action_6 (98) = happyShift action_121 action_6 (102) = happyShift action_122 action_6 (103) = happyShift action_123 action_6 (104) = happyShift action_124 action_6 (106) = happyShift action_125 action_6 (107) = happyShift action_126 action_6 (118) = happyShift action_63 action_6 (40) = happyGoto action_103 action_6 (47) = happyGoto action_113 action_6 (51) = happyGoto action_114 action_6 (52) = happyGoto action_109 action_6 _ = happyFail (happyExpListPerState 6) action_7 (86) = happyShift action_62 action_7 (114) = happyShift action_34 action_7 (118) = happyShift action_63 action_7 (36) = happyGoto action_55 action_7 (40) = happyGoto action_56 action_7 (48) = happyGoto action_112 action_7 (50) = happyGoto action_59 action_7 _ = happyFail (happyExpListPerState 7) action_8 (86) = happyShift action_62 action_8 (114) = happyShift action_34 action_8 (118) = happyShift action_63 action_8 (36) = happyGoto action_55 action_8 (40) = happyGoto action_56 action_8 (48) = happyGoto action_57 action_8 (49) = happyGoto action_111 action_8 (50) = happyGoto action_59 action_8 _ = happyReduce_71 action_9 (86) = happyShift action_62 action_9 (118) = happyShift action_63 action_9 (40) = happyGoto action_56 action_9 (50) = happyGoto action_110 action_9 _ = happyFail (happyExpListPerState 9) action_10 (74) = happyShift action_105 action_10 (86) = happyShift action_106 action_10 (88) = happyShift action_107 action_10 (118) = happyShift action_63 action_10 (40) = happyGoto action_103 action_10 (51) = happyGoto action_108 action_10 (52) = happyGoto action_109 action_10 _ = happyFail (happyExpListPerState 10) action_11 (74) = happyShift action_105 action_11 (86) = happyShift action_106 action_11 (88) = happyShift action_107 action_11 (118) = happyShift action_63 action_11 (40) = happyGoto action_103 action_11 (52) = happyGoto action_104 action_11 _ = happyFail (happyExpListPerState 11) action_12 (74) = happyShift action_95 action_12 (53) = happyGoto action_102 action_12 _ = happyFail (happyExpListPerState 12) action_13 (86) = happyShift action_98 action_13 (54) = happyGoto action_101 action_13 _ = happyFail (happyExpListPerState 13) action_14 (115) = happyShift action_74 action_14 (37) = happyGoto action_99 action_14 (55) = happyGoto action_100 action_14 _ = happyReduce_86 action_15 (86) = happyShift action_98 action_15 (54) = happyGoto action_96 action_15 (56) = happyGoto action_97 action_15 _ = happyReduce_89 action_16 (74) = happyShift action_95 action_16 (53) = happyGoto action_93 action_16 (57) = happyGoto action_94 action_16 _ = happyFail (happyExpListPerState 16) action_17 (118) = happyShift action_63 action_17 (40) = happyGoto action_89 action_17 (58) = happyGoto action_92 action_17 _ = happyFail (happyExpListPerState 17) action_18 (118) = happyShift action_63 action_18 (40) = happyGoto action_89 action_18 (58) = happyGoto action_90 action_18 (59) = happyGoto action_91 action_18 _ = happyReduce_95 action_19 (104) = happyShift action_87 action_19 (106) = happyShift action_88 action_19 (60) = happyGoto action_86 action_19 _ = happyReduce_97 action_20 (114) = happyShift action_34 action_20 (36) = happyGoto action_84 action_20 (61) = happyGoto action_85 action_20 _ = happyFail (happyExpListPerState 20) action_21 (74) = happyShift action_72 action_21 (86) = happyShift action_73 action_21 (114) = happyShift action_34 action_21 (115) = happyShift action_74 action_21 (116) = happyShift action_46 action_21 (117) = happyShift action_75 action_21 (118) = happyShift action_63 action_21 (36) = happyGoto action_65 action_21 (37) = happyGoto action_66 action_21 (38) = happyGoto action_67 action_21 (39) = happyGoto action_68 action_21 (40) = happyGoto action_76 action_21 (62) = happyGoto action_83 action_21 (63) = happyGoto action_78 action_21 (64) = happyGoto action_79 action_21 _ = happyFail (happyExpListPerState 21) action_22 (74) = happyShift action_72 action_22 (86) = happyShift action_73 action_22 (114) = happyShift action_34 action_22 (115) = happyShift action_74 action_22 (116) = happyShift action_46 action_22 (117) = happyShift action_75 action_22 (118) = happyShift action_63 action_22 (36) = happyGoto action_65 action_22 (37) = happyGoto action_66 action_22 (38) = happyGoto action_67 action_22 (39) = happyGoto action_68 action_22 (40) = happyGoto action_76 action_22 (63) = happyGoto action_82 action_22 (64) = happyGoto action_79 action_22 _ = happyFail (happyExpListPerState 22) action_23 (74) = happyShift action_72 action_23 (86) = happyShift action_73 action_23 (114) = happyShift action_34 action_23 (115) = happyShift action_74 action_23 (116) = happyShift action_46 action_23 (117) = happyShift action_75 action_23 (118) = happyShift action_63 action_23 (36) = happyGoto action_65 action_23 (37) = happyGoto action_66 action_23 (38) = happyGoto action_67 action_23 (39) = happyGoto action_68 action_23 (40) = happyGoto action_69 action_23 (64) = happyGoto action_81 action_23 _ = happyFail (happyExpListPerState 23) action_24 (74) = happyShift action_72 action_24 (86) = happyShift action_73 action_24 (114) = happyShift action_34 action_24 (115) = happyShift action_74 action_24 (116) = happyShift action_46 action_24 (117) = happyShift action_75 action_24 (118) = happyShift action_63 action_24 (36) = happyGoto action_65 action_24 (37) = happyGoto action_66 action_24 (38) = happyGoto action_67 action_24 (39) = happyGoto action_68 action_24 (40) = happyGoto action_76 action_24 (62) = happyGoto action_77 action_24 (63) = happyGoto action_78 action_24 (64) = happyGoto action_79 action_24 (65) = happyGoto action_80 action_24 _ = happyReduce_113 action_25 (74) = happyShift action_72 action_25 (86) = happyShift action_73 action_25 (114) = happyShift action_34 action_25 (115) = happyShift action_74 action_25 (116) = happyShift action_46 action_25 (117) = happyShift action_75 action_25 (118) = happyShift action_63 action_25 (36) = happyGoto action_65 action_25 (37) = happyGoto action_66 action_25 (38) = happyGoto action_67 action_25 (39) = happyGoto action_68 action_25 (40) = happyGoto action_69 action_25 (64) = happyGoto action_70 action_25 (66) = happyGoto action_71 action_25 _ = happyFail (happyExpListPerState 25) action_26 (86) = happyShift action_62 action_26 (114) = happyShift action_34 action_26 (118) = happyShift action_63 action_26 (36) = happyGoto action_55 action_26 (40) = happyGoto action_56 action_26 (48) = happyGoto action_57 action_26 (49) = happyGoto action_58 action_26 (50) = happyGoto action_59 action_26 (67) = happyGoto action_64 action_26 _ = happyReduce_71 action_27 (86) = happyShift action_62 action_27 (114) = happyShift action_34 action_27 (118) = happyShift action_63 action_27 (36) = happyGoto action_55 action_27 (40) = happyGoto action_56 action_27 (48) = happyGoto action_57 action_27 (49) = happyGoto action_58 action_27 (50) = happyGoto action_59 action_27 (67) = happyGoto action_60 action_27 (68) = happyGoto action_61 action_27 _ = happyReduce_71 action_28 (101) = happyShift action_54 action_28 (69) = happyGoto action_53 action_28 _ = happyReduce_122 action_29 (74) = happyShift action_37 action_29 (86) = happyShift action_38 action_29 (89) = happyShift action_39 action_29 (94) = happyShift action_40 action_29 (96) = happyShift action_41 action_29 (99) = happyShift action_42 action_29 (100) = happyShift action_43 action_29 (109) = happyShift action_44 action_29 (111) = happyShift action_45 action_29 (116) = happyShift action_46 action_29 (38) = happyGoto action_35 action_29 (70) = happyGoto action_51 action_29 (71) = happyGoto action_52 action_29 (72) = happyGoto action_50 action_29 (73) = happyGoto action_48 action_29 _ = happyFail (happyExpListPerState 29) action_30 (74) = happyShift action_37 action_30 (86) = happyShift action_38 action_30 (89) = happyShift action_39 action_30 (94) = happyShift action_40 action_30 (96) = happyShift action_41 action_30 (99) = happyShift action_42 action_30 (100) = happyShift action_43 action_30 (109) = happyShift action_44 action_30 (111) = happyShift action_45 action_30 (116) = happyShift action_46 action_30 (38) = happyGoto action_35 action_30 (71) = happyGoto action_49 action_30 (72) = happyGoto action_50 action_30 (73) = happyGoto action_48 action_30 _ = happyFail (happyExpListPerState 30) action_31 (74) = happyShift action_37 action_31 (86) = happyShift action_38 action_31 (89) = happyShift action_39 action_31 (94) = happyShift action_40 action_31 (96) = happyShift action_41 action_31 (99) = happyShift action_42 action_31 (100) = happyShift action_43 action_31 (109) = happyShift action_44 action_31 (111) = happyShift action_45 action_31 (116) = happyShift action_46 action_31 (38) = happyGoto action_35 action_31 (72) = happyGoto action_47 action_31 (73) = happyGoto action_48 action_31 _ = happyFail (happyExpListPerState 31) action_32 (74) = happyShift action_37 action_32 (86) = happyShift action_38 action_32 (89) = happyShift action_39 action_32 (94) = happyShift action_40 action_32 (96) = happyShift action_41 action_32 (99) = happyShift action_42 action_32 (100) = happyShift action_43 action_32 (109) = happyShift action_44 action_32 (111) = happyShift action_45 action_32 (116) = happyShift action_46 action_32 (38) = happyGoto action_35 action_32 (73) = happyGoto action_36 action_32 _ = happyFail (happyExpListPerState 32) action_33 (114) = happyShift action_34 action_33 _ = happyFail (happyExpListPerState 33) action_34 _ = happyReduce_33 action_35 _ = happyReduce_133 action_36 (76) = happyShift action_192 action_36 (77) = happyShift action_193 action_36 (85) = happyShift action_194 action_36 (119) = happyAccept action_36 _ = happyFail (happyExpListPerState 36) action_37 (74) = happyShift action_37 action_37 (86) = happyShift action_38 action_37 (89) = happyShift action_39 action_37 (94) = happyShift action_40 action_37 (96) = happyShift action_41 action_37 (99) = happyShift action_42 action_37 (100) = happyShift action_43 action_37 (109) = happyShift action_44 action_37 (111) = happyShift action_45 action_37 (116) = happyShift action_46 action_37 (38) = happyGoto action_35 action_37 (70) = happyGoto action_197 action_37 (71) = happyGoto action_52 action_37 (72) = happyGoto action_50 action_37 (73) = happyGoto action_48 action_37 _ = happyFail (happyExpListPerState 37) action_38 (114) = happyShift action_34 action_38 (36) = happyGoto action_196 action_38 _ = happyFail (happyExpListPerState 38) action_39 _ = happyReduce_140 action_40 _ = happyReduce_136 action_41 _ = happyReduce_132 action_42 _ = happyReduce_137 action_43 _ = happyReduce_139 action_44 _ = happyReduce_138 action_45 (114) = happyShift action_34 action_45 (36) = happyGoto action_195 action_45 _ = happyFail (happyExpListPerState 45) action_46 _ = happyReduce_35 action_47 (74) = happyShift action_37 action_47 (86) = happyShift action_38 action_47 (89) = happyShift action_39 action_47 (94) = happyShift action_40 action_47 (96) = happyShift action_41 action_47 (99) = happyShift action_42 action_47 (100) = happyShift action_43 action_47 (109) = happyShift action_44 action_47 (111) = happyShift action_45 action_47 (116) = happyShift action_46 action_47 (119) = happyAccept action_47 (38) = happyGoto action_35 action_47 (73) = happyGoto action_191 action_47 _ = happyFail (happyExpListPerState 47) action_48 (76) = happyShift action_192 action_48 (77) = happyShift action_193 action_48 (85) = happyShift action_194 action_48 _ = happyReduce_128 action_49 (79) = happyShift action_189 action_49 (119) = happyAccept action_49 _ = happyFail (happyExpListPerState 49) action_50 (74) = happyShift action_37 action_50 (86) = happyShift action_38 action_50 (89) = happyShift action_39 action_50 (94) = happyShift action_40 action_50 (96) = happyShift action_41 action_50 (99) = happyShift action_42 action_50 (100) = happyShift action_43 action_50 (109) = happyShift action_44 action_50 (111) = happyShift action_45 action_50 (116) = happyShift action_46 action_50 (38) = happyGoto action_35 action_50 (73) = happyGoto action_191 action_50 _ = happyReduce_126 action_51 (112) = happyShift action_190 action_51 (119) = happyAccept action_51 _ = happyFail (happyExpListPerState 51) action_52 (79) = happyShift action_189 action_52 _ = happyReduce_124 action_53 (119) = happyAccept action_53 _ = happyFail (happyExpListPerState 53) action_54 _ = happyReduce_121 action_55 _ = happyReduce_69 action_56 _ = happyReduce_74 action_57 (86) = happyShift action_62 action_57 (114) = happyShift action_34 action_57 (118) = happyShift action_63 action_57 (36) = happyGoto action_55 action_57 (40) = happyGoto action_56 action_57 (48) = happyGoto action_57 action_57 (49) = happyGoto action_188 action_57 (50) = happyGoto action_59 action_57 _ = happyReduce_71 action_58 _ = happyReduce_118 action_59 _ = happyReduce_70 action_60 (112) = happyShift action_187 action_60 _ = happyReduce_119 action_61 (119) = happyAccept action_61 _ = happyFail (happyExpListPerState 61) action_62 (86) = happyShift action_62 action_62 (118) = happyShift action_63 action_62 (40) = happyGoto action_56 action_62 (50) = happyGoto action_186 action_62 _ = happyFail (happyExpListPerState 62) action_63 _ = happyReduce_37 action_64 (119) = happyAccept action_64 _ = happyFail (happyExpListPerState 64) action_65 _ = happyReduce_109 action_66 _ = happyReduce_107 action_67 _ = happyReduce_108 action_68 _ = happyReduce_110 action_69 _ = happyReduce_106 action_70 (74) = happyShift action_72 action_70 (86) = happyShift action_73 action_70 (114) = happyShift action_34 action_70 (115) = happyShift action_74 action_70 (116) = happyShift action_46 action_70 (117) = happyShift action_75 action_70 (118) = happyShift action_63 action_70 (36) = happyGoto action_65 action_70 (37) = happyGoto action_66 action_70 (38) = happyGoto action_67 action_70 (39) = happyGoto action_68 action_70 (40) = happyGoto action_69 action_70 (64) = happyGoto action_70 action_70 (66) = happyGoto action_185 action_70 _ = happyReduce_116 action_71 (119) = happyAccept action_71 _ = happyFail (happyExpListPerState 71) action_72 (74) = happyShift action_72 action_72 (86) = happyShift action_73 action_72 (114) = happyShift action_34 action_72 (115) = happyShift action_74 action_72 (116) = happyShift action_46 action_72 (117) = happyShift action_75 action_72 (118) = happyShift action_63 action_72 (36) = happyGoto action_65 action_72 (37) = happyGoto action_66 action_72 (38) = happyGoto action_67 action_72 (39) = happyGoto action_68 action_72 (40) = happyGoto action_76 action_72 (62) = happyGoto action_184 action_72 (63) = happyGoto action_78 action_72 (64) = happyGoto action_79 action_72 _ = happyFail (happyExpListPerState 72) action_73 (74) = happyShift action_72 action_73 (86) = happyShift action_73 action_73 (114) = happyShift action_34 action_73 (115) = happyShift action_74 action_73 (116) = happyShift action_46 action_73 (117) = happyShift action_75 action_73 (118) = happyShift action_63 action_73 (36) = happyGoto action_65 action_73 (37) = happyGoto action_66 action_73 (38) = happyGoto action_67 action_73 (39) = happyGoto action_68 action_73 (40) = happyGoto action_76 action_73 (62) = happyGoto action_77 action_73 (63) = happyGoto action_78 action_73 (64) = happyGoto action_79 action_73 (65) = happyGoto action_183 action_73 _ = happyReduce_113 action_74 _ = happyReduce_34 action_75 _ = happyReduce_36 action_76 (74) = happyShift action_72 action_76 (86) = happyShift action_73 action_76 (114) = happyShift action_34 action_76 (115) = happyShift action_74 action_76 (116) = happyShift action_46 action_76 (117) = happyShift action_75 action_76 (118) = happyShift action_63 action_76 (36) = happyGoto action_65 action_76 (37) = happyGoto action_66 action_76 (38) = happyGoto action_67 action_76 (39) = happyGoto action_68 action_76 (40) = happyGoto action_69 action_76 (64) = happyGoto action_70 action_76 (66) = happyGoto action_182 action_76 _ = happyReduce_106 action_77 (78) = happyShift action_181 action_77 _ = happyReduce_114 action_78 (81) = happyShift action_180 action_78 _ = happyReduce_103 action_79 _ = happyReduce_105 action_80 (119) = happyAccept action_80 _ = happyFail (happyExpListPerState 80) action_81 (119) = happyAccept action_81 _ = happyFail (happyExpListPerState 81) action_82 (119) = happyAccept action_82 _ = happyFail (happyExpListPerState 82) action_83 (119) = happyAccept action_83 _ = happyFail (happyExpListPerState 83) action_84 (78) = happyShift action_179 action_84 _ = happyReduce_100 action_85 (119) = happyAccept action_85 _ = happyFail (happyExpListPerState 85) action_86 (119) = happyAccept action_86 _ = happyFail (happyExpListPerState 86) action_87 (114) = happyShift action_34 action_87 (36) = happyGoto action_178 action_87 _ = happyFail (happyExpListPerState 87) action_88 (114) = happyShift action_34 action_88 (36) = happyGoto action_177 action_88 _ = happyFail (happyExpListPerState 88) action_89 _ = happyReduce_94 action_90 (118) = happyShift action_63 action_90 (40) = happyGoto action_89 action_90 (58) = happyGoto action_90 action_90 (59) = happyGoto action_176 action_90 _ = happyReduce_95 action_91 (119) = happyAccept action_91 _ = happyFail (happyExpListPerState 91) action_92 (119) = happyAccept action_92 _ = happyFail (happyExpListPerState 92) action_93 (74) = happyShift action_95 action_93 (53) = happyGoto action_93 action_93 (57) = happyGoto action_175 action_93 _ = happyReduce_92 action_94 (119) = happyAccept action_94 _ = happyFail (happyExpListPerState 94) action_95 (86) = happyShift action_174 action_95 _ = happyFail (happyExpListPerState 95) action_96 (78) = happyShift action_173 action_96 _ = happyReduce_90 action_97 (119) = happyAccept action_97 _ = happyFail (happyExpListPerState 97) action_98 (115) = happyShift action_74 action_98 (37) = happyGoto action_99 action_98 (55) = happyGoto action_172 action_98 _ = happyReduce_86 action_99 (78) = happyShift action_171 action_99 _ = happyReduce_87 action_100 (119) = happyAccept action_100 _ = happyFail (happyExpListPerState 100) action_101 (119) = happyAccept action_101 _ = happyFail (happyExpListPerState 101) action_102 (119) = happyAccept action_102 _ = happyFail (happyExpListPerState 102) action_103 _ = happyReduce_79 action_104 (119) = happyAccept action_104 _ = happyFail (happyExpListPerState 104) action_105 (81) = happyShift action_170 action_105 _ = happyFail (happyExpListPerState 105) action_106 (87) = happyShift action_169 action_106 _ = happyFail (happyExpListPerState 106) action_107 _ = happyReduce_80 action_108 (119) = happyAccept action_108 _ = happyFail (happyExpListPerState 108) action_109 (74) = happyShift action_168 action_109 (86) = happyShift action_106 action_109 (88) = happyShift action_107 action_109 (118) = happyShift action_63 action_109 (40) = happyGoto action_103 action_109 (52) = happyGoto action_166 action_109 (53) = happyGoto action_93 action_109 (57) = happyGoto action_167 action_109 _ = happyReduce_75 action_110 (119) = happyAccept action_110 _ = happyFail (happyExpListPerState 110) action_111 (119) = happyAccept action_111 _ = happyFail (happyExpListPerState 111) action_112 (119) = happyAccept action_112 _ = happyFail (happyExpListPerState 112) action_113 (119) = happyAccept action_113 _ = happyFail (happyExpListPerState 113) action_114 (80) = happyShift action_165 action_114 _ = happyFail (happyExpListPerState 114) action_115 (118) = happyShift action_63 action_115 (40) = happyGoto action_164 action_115 _ = happyFail (happyExpListPerState 115) action_116 (114) = happyShift action_34 action_116 (36) = happyGoto action_163 action_116 _ = happyFail (happyExpListPerState 116) action_117 (118) = happyShift action_63 action_117 (40) = happyGoto action_162 action_117 _ = happyFail (happyExpListPerState 117) action_118 (86) = happyShift action_62 action_118 (118) = happyShift action_63 action_118 (40) = happyGoto action_56 action_118 (50) = happyGoto action_161 action_118 _ = happyFail (happyExpListPerState 118) action_119 (118) = happyShift action_63 action_119 (40) = happyGoto action_132 action_119 (44) = happyGoto action_160 action_119 _ = happyFail (happyExpListPerState 119) action_120 (74) = happyShift action_105 action_120 (86) = happyShift action_106 action_120 (88) = happyShift action_107 action_120 (118) = happyShift action_63 action_120 (40) = happyGoto action_103 action_120 (51) = happyGoto action_159 action_120 (52) = happyGoto action_109 action_120 _ = happyFail (happyExpListPerState 120) action_121 (105) = happyShift action_157 action_121 (108) = happyShift action_158 action_121 (114) = happyShift action_34 action_121 (36) = happyGoto action_84 action_121 (61) = happyGoto action_156 action_121 _ = happyFail (happyExpListPerState 121) action_122 (107) = happyShift action_155 action_122 _ = happyFail (happyExpListPerState 122) action_123 (118) = happyShift action_63 action_123 (40) = happyGoto action_154 action_123 _ = happyFail (happyExpListPerState 123) action_124 (101) = happyShift action_54 action_124 (69) = happyGoto action_153 action_124 _ = happyReduce_122 action_125 (101) = happyShift action_54 action_125 (69) = happyGoto action_152 action_125 _ = happyReduce_122 action_126 (118) = happyShift action_63 action_126 (40) = happyGoto action_151 action_126 _ = happyFail (happyExpListPerState 126) action_127 (119) = happyAccept action_127 _ = happyFail (happyExpListPerState 127) action_128 (83) = happyShift action_150 action_128 _ = happyReduce_50 action_129 (74) = happyShift action_105 action_129 (83) = happyShift action_129 action_129 (86) = happyShift action_106 action_129 (88) = happyShift action_107 action_129 (90) = happyShift action_115 action_129 (91) = happyShift action_116 action_129 (92) = happyShift action_117 action_129 (93) = happyShift action_118 action_129 (95) = happyShift action_119 action_129 (97) = happyShift action_120 action_129 (98) = happyShift action_121 action_129 (102) = happyShift action_122 action_129 (103) = happyShift action_123 action_129 (104) = happyShift action_124 action_129 (106) = happyShift action_125 action_129 (107) = happyShift action_126 action_129 (118) = happyShift action_63 action_129 (40) = happyGoto action_103 action_129 (46) = happyGoto action_149 action_129 (47) = happyGoto action_128 action_129 (51) = happyGoto action_114 action_129 (52) = happyGoto action_109 action_129 _ = happyReduce_49 action_130 (119) = happyAccept action_130 _ = happyFail (happyExpListPerState 130) action_131 _ = happyReduce_48 action_132 (78) = happyShift action_148 action_132 _ = happyReduce_46 action_133 (119) = happyAccept action_133 _ = happyFail (happyExpListPerState 133) action_134 (78) = happyShift action_148 action_134 (81) = happyReduce_46 action_134 _ = happyReduce_79 action_135 (83) = happyShift action_147 action_135 _ = happyReduce_43 action_136 (119) = happyAccept action_136 _ = happyFail (happyExpListPerState 136) action_137 (81) = happyShift action_146 action_137 _ = happyFail (happyExpListPerState 137) action_138 _ = happyReduce_39 action_139 (74) = happyShift action_105 action_139 (83) = happyShift action_139 action_139 (86) = happyShift action_106 action_139 (88) = happyShift action_107 action_139 (90) = happyShift action_115 action_139 (91) = happyShift action_116 action_139 (92) = happyShift action_117 action_139 (93) = happyShift action_118 action_139 (95) = happyShift action_119 action_139 (97) = happyShift action_120 action_139 (98) = happyShift action_121 action_139 (102) = happyShift action_122 action_139 (103) = happyShift action_123 action_139 (104) = happyShift action_124 action_139 (106) = happyShift action_125 action_139 (107) = happyShift action_126 action_139 (110) = happyShift action_140 action_139 (118) = happyShift action_63 action_139 (40) = happyGoto action_134 action_139 (42) = happyGoto action_135 action_139 (43) = happyGoto action_145 action_139 (44) = happyGoto action_137 action_139 (47) = happyGoto action_138 action_139 (51) = happyGoto action_114 action_139 (52) = happyGoto action_109 action_139 _ = happyReduce_42 action_140 (118) = happyShift action_63 action_140 (40) = happyGoto action_132 action_140 (44) = happyGoto action_144 action_140 _ = happyFail (happyExpListPerState 140) action_141 (119) = happyAccept action_141 _ = happyFail (happyExpListPerState 141) action_142 (119) = happyAccept action_142 _ = happyFail (happyExpListPerState 142) action_143 _ = happyReduce_38 action_144 _ = happyReduce_41 action_145 _ = happyReduce_45 action_146 (74) = happyShift action_105 action_146 (86) = happyShift action_106 action_146 (88) = happyShift action_107 action_146 (90) = happyShift action_115 action_146 (91) = happyShift action_116 action_146 (92) = happyShift action_117 action_146 (93) = happyShift action_118 action_146 (95) = happyShift action_119 action_146 (97) = happyShift action_120 action_146 (98) = happyShift action_121 action_146 (102) = happyShift action_122 action_146 (103) = happyShift action_123 action_146 (104) = happyShift action_124 action_146 (106) = happyShift action_125 action_146 (107) = happyShift action_126 action_146 (118) = happyShift action_63 action_146 (40) = happyGoto action_103 action_146 (47) = happyGoto action_232 action_146 (51) = happyGoto action_114 action_146 (52) = happyGoto action_109 action_146 _ = happyFail (happyExpListPerState 146) action_147 (74) = happyShift action_105 action_147 (83) = happyShift action_139 action_147 (86) = happyShift action_106 action_147 (88) = happyShift action_107 action_147 (90) = happyShift action_115 action_147 (91) = happyShift action_116 action_147 (92) = happyShift action_117 action_147 (93) = happyShift action_118 action_147 (95) = happyShift action_119 action_147 (97) = happyShift action_120 action_147 (98) = happyShift action_121 action_147 (102) = happyShift action_122 action_147 (103) = happyShift action_123 action_147 (104) = happyShift action_124 action_147 (106) = happyShift action_125 action_147 (107) = happyShift action_126 action_147 (110) = happyShift action_140 action_147 (118) = happyShift action_63 action_147 (40) = happyGoto action_134 action_147 (42) = happyGoto action_135 action_147 (43) = happyGoto action_231 action_147 (44) = happyGoto action_137 action_147 (47) = happyGoto action_138 action_147 (51) = happyGoto action_114 action_147 (52) = happyGoto action_109 action_147 _ = happyReduce_42 action_148 (118) = happyShift action_63 action_148 (40) = happyGoto action_132 action_148 (44) = happyGoto action_230 action_148 _ = happyFail (happyExpListPerState 148) action_149 _ = happyReduce_52 action_150 (74) = happyShift action_105 action_150 (83) = happyShift action_129 action_150 (86) = happyShift action_106 action_150 (88) = happyShift action_107 action_150 (90) = happyShift action_115 action_150 (91) = happyShift action_116 action_150 (92) = happyShift action_117 action_150 (93) = happyShift action_118 action_150 (95) = happyShift action_119 action_150 (97) = happyShift action_120 action_150 (98) = happyShift action_121 action_150 (102) = happyShift action_122 action_150 (103) = happyShift action_123 action_150 (104) = happyShift action_124 action_150 (106) = happyShift action_125 action_150 (107) = happyShift action_126 action_150 (118) = happyShift action_63 action_150 (40) = happyGoto action_103 action_150 (46) = happyGoto action_229 action_150 (47) = happyGoto action_128 action_150 (51) = happyGoto action_114 action_150 (52) = happyGoto action_109 action_150 _ = happyReduce_49 action_151 (74) = happyShift action_37 action_151 (86) = happyShift action_38 action_151 (89) = happyShift action_39 action_151 (94) = happyShift action_40 action_151 (96) = happyShift action_41 action_151 (99) = happyShift action_42 action_151 (100) = happyShift action_43 action_151 (109) = happyShift action_44 action_151 (111) = happyShift action_45 action_151 (116) = happyShift action_46 action_151 (38) = happyGoto action_35 action_151 (70) = happyGoto action_228 action_151 (71) = happyGoto action_52 action_151 (72) = happyGoto action_50 action_151 (73) = happyGoto action_48 action_151 _ = happyFail (happyExpListPerState 151) action_152 (86) = happyShift action_62 action_152 (118) = happyShift action_63 action_152 (40) = happyGoto action_56 action_152 (50) = happyGoto action_227 action_152 _ = happyFail (happyExpListPerState 152) action_153 (86) = happyShift action_62 action_153 (118) = happyShift action_63 action_153 (40) = happyGoto action_56 action_153 (50) = happyGoto action_226 action_153 _ = happyFail (happyExpListPerState 153) action_154 (82) = happyShift action_225 action_154 _ = happyFail (happyExpListPerState 154) action_155 (118) = happyShift action_63 action_155 (40) = happyGoto action_224 action_155 _ = happyFail (happyExpListPerState 155) action_156 _ = happyReduce_66 action_157 (114) = happyShift action_34 action_157 (36) = happyGoto action_84 action_157 (61) = happyGoto action_223 action_157 _ = happyFail (happyExpListPerState 157) action_158 _ = happyReduce_68 action_159 (80) = happyShift action_222 action_159 _ = happyFail (happyExpListPerState 159) action_160 _ = happyReduce_59 action_161 (114) = happyShift action_34 action_161 (36) = happyGoto action_221 action_161 _ = happyFail (happyExpListPerState 161) action_162 (118) = happyShift action_63 action_162 (40) = happyGoto action_89 action_162 (58) = happyGoto action_90 action_162 (59) = happyGoto action_220 action_162 _ = happyReduce_95 action_163 (114) = happyShift action_34 action_163 (36) = happyGoto action_219 action_163 _ = happyReduce_54 action_164 (115) = happyShift action_74 action_164 (37) = happyGoto action_218 action_164 _ = happyFail (happyExpListPerState 164) action_165 (86) = happyShift action_62 action_165 (118) = happyShift action_63 action_165 (40) = happyGoto action_56 action_165 (50) = happyGoto action_217 action_165 _ = happyFail (happyExpListPerState 165) action_166 (74) = happyShift action_95 action_166 (53) = happyGoto action_93 action_166 (57) = happyGoto action_216 action_166 _ = happyReduce_78 action_167 _ = happyReduce_76 action_168 (81) = happyShift action_170 action_168 (86) = happyShift action_174 action_168 _ = happyFail (happyExpListPerState 168) action_169 _ = happyReduce_81 action_170 (75) = happyShift action_214 action_170 (86) = happyShift action_215 action_170 _ = happyFail (happyExpListPerState 170) action_171 (115) = happyShift action_74 action_171 (37) = happyGoto action_99 action_171 (55) = happyGoto action_213 action_171 _ = happyReduce_86 action_172 (87) = happyShift action_212 action_172 _ = happyFail (happyExpListPerState 172) action_173 (86) = happyShift action_98 action_173 (54) = happyGoto action_96 action_173 (56) = happyGoto action_211 action_173 _ = happyReduce_89 action_174 (86) = happyShift action_98 action_174 (54) = happyGoto action_96 action_174 (56) = happyGoto action_210 action_174 _ = happyReduce_89 action_175 _ = happyReduce_93 action_176 _ = happyReduce_96 action_177 _ = happyReduce_98 action_178 _ = happyReduce_99 action_179 (114) = happyShift action_34 action_179 (36) = happyGoto action_84 action_179 (61) = happyGoto action_209 action_179 _ = happyFail (happyExpListPerState 179) action_180 (74) = happyShift action_72 action_180 (86) = happyShift action_73 action_180 (114) = happyShift action_34 action_180 (115) = happyShift action_74 action_180 (116) = happyShift action_46 action_180 (117) = happyShift action_75 action_180 (118) = happyShift action_63 action_180 (36) = happyGoto action_65 action_180 (37) = happyGoto action_66 action_180 (38) = happyGoto action_67 action_180 (39) = happyGoto action_68 action_180 (40) = happyGoto action_76 action_180 (62) = happyGoto action_208 action_180 (63) = happyGoto action_78 action_180 (64) = happyGoto action_79 action_180 _ = happyFail (happyExpListPerState 180) action_181 (74) = happyShift action_72 action_181 (86) = happyShift action_73 action_181 (114) = happyShift action_34 action_181 (115) = happyShift action_74 action_181 (116) = happyShift action_46 action_181 (117) = happyShift action_75 action_181 (118) = happyShift action_63 action_181 (36) = happyGoto action_65 action_181 (37) = happyGoto action_66 action_181 (38) = happyGoto action_67 action_181 (39) = happyGoto action_68 action_181 (40) = happyGoto action_76 action_181 (62) = happyGoto action_77 action_181 (63) = happyGoto action_78 action_181 (64) = happyGoto action_79 action_181 (65) = happyGoto action_207 action_181 _ = happyReduce_113 action_182 _ = happyReduce_104 action_183 (87) = happyShift action_206 action_183 _ = happyFail (happyExpListPerState 183) action_184 (75) = happyShift action_205 action_184 _ = happyFail (happyExpListPerState 184) action_185 _ = happyReduce_117 action_186 (87) = happyShift action_204 action_186 _ = happyFail (happyExpListPerState 186) action_187 (86) = happyShift action_62 action_187 (114) = happyShift action_34 action_187 (118) = happyShift action_63 action_187 (36) = happyGoto action_55 action_187 (40) = happyGoto action_56 action_187 (48) = happyGoto action_57 action_187 (49) = happyGoto action_58 action_187 (50) = happyGoto action_59 action_187 (67) = happyGoto action_60 action_187 (68) = happyGoto action_203 action_187 _ = happyReduce_71 action_188 _ = happyReduce_72 action_189 (74) = happyShift action_37 action_189 (86) = happyShift action_38 action_189 (89) = happyShift action_39 action_189 (94) = happyShift action_40 action_189 (96) = happyShift action_41 action_189 (99) = happyShift action_42 action_189 (100) = happyShift action_43 action_189 (109) = happyShift action_44 action_189 (111) = happyShift action_45 action_189 (116) = happyShift action_46 action_189 (38) = happyGoto action_35 action_189 (72) = happyGoto action_202 action_189 (73) = happyGoto action_48 action_189 _ = happyFail (happyExpListPerState 189) action_190 (74) = happyShift action_37 action_190 (86) = happyShift action_38 action_190 (89) = happyShift action_39 action_190 (94) = happyShift action_40 action_190 (96) = happyShift action_41 action_190 (99) = happyShift action_42 action_190 (100) = happyShift action_43 action_190 (109) = happyShift action_44 action_190 (111) = happyShift action_45 action_190 (116) = happyShift action_46 action_190 (38) = happyGoto action_35 action_190 (71) = happyGoto action_201 action_190 (72) = happyGoto action_50 action_190 (73) = happyGoto action_48 action_190 _ = happyFail (happyExpListPerState 190) action_191 (76) = happyShift action_192 action_191 (77) = happyShift action_193 action_191 (85) = happyShift action_194 action_191 _ = happyReduce_127 action_192 _ = happyReduce_129 action_193 _ = happyReduce_130 action_194 _ = happyReduce_131 action_195 (113) = happyShift action_200 action_195 _ = happyFail (happyExpListPerState 195) action_196 (87) = happyShift action_199 action_196 _ = happyFail (happyExpListPerState 196) action_197 (75) = happyShift action_198 action_197 (112) = happyShift action_190 action_197 _ = happyFail (happyExpListPerState 197) action_198 _ = happyReduce_141 action_199 _ = happyReduce_134 action_200 _ = happyReduce_135 action_201 (79) = happyShift action_189 action_201 _ = happyReduce_123 action_202 (74) = happyShift action_37 action_202 (86) = happyShift action_38 action_202 (89) = happyShift action_39 action_202 (94) = happyShift action_40 action_202 (96) = happyShift action_41 action_202 (99) = happyShift action_42 action_202 (100) = happyShift action_43 action_202 (109) = happyShift action_44 action_202 (111) = happyShift action_45 action_202 (116) = happyShift action_46 action_202 (38) = happyGoto action_35 action_202 (73) = happyGoto action_191 action_202 _ = happyReduce_125 action_203 _ = happyReduce_120 action_204 _ = happyReduce_73 action_205 _ = happyReduce_112 action_206 _ = happyReduce_111 action_207 _ = happyReduce_115 action_208 _ = happyReduce_102 action_209 _ = happyReduce_101 action_210 (87) = happyShift action_242 action_210 _ = happyFail (happyExpListPerState 210) action_211 _ = happyReduce_91 action_212 _ = happyReduce_85 action_213 _ = happyReduce_88 action_214 _ = happyReduce_82 action_215 (87) = happyShift action_241 action_215 _ = happyFail (happyExpListPerState 215) action_216 _ = happyReduce_77 action_217 (82) = happyShift action_240 action_217 _ = happyFail (happyExpListPerState 217) action_218 _ = happyReduce_63 action_219 _ = happyReduce_55 action_220 (84) = happyShift action_239 action_220 _ = happyFail (happyExpListPerState 220) action_221 (114) = happyShift action_34 action_221 (36) = happyGoto action_238 action_221 _ = happyFail (happyExpListPerState 221) action_222 (86) = happyShift action_62 action_222 (118) = happyShift action_63 action_222 (40) = happyGoto action_56 action_222 (50) = happyGoto action_237 action_222 _ = happyFail (happyExpListPerState 222) action_223 _ = happyReduce_67 action_224 (74) = happyShift action_37 action_224 (86) = happyShift action_38 action_224 (89) = happyShift action_39 action_224 (94) = happyShift action_40 action_224 (96) = happyShift action_41 action_224 (99) = happyShift action_42 action_224 (100) = happyShift action_43 action_224 (109) = happyShift action_44 action_224 (111) = happyShift action_45 action_224 (116) = happyShift action_46 action_224 (38) = happyGoto action_35 action_224 (70) = happyGoto action_236 action_224 (71) = happyGoto action_52 action_224 (72) = happyGoto action_50 action_224 (73) = happyGoto action_48 action_224 _ = happyFail (happyExpListPerState 224) action_225 (86) = happyShift action_62 action_225 (114) = happyShift action_34 action_225 (118) = happyShift action_63 action_225 (36) = happyGoto action_55 action_225 (40) = happyGoto action_56 action_225 (48) = happyGoto action_57 action_225 (49) = happyGoto action_58 action_225 (50) = happyGoto action_59 action_225 (67) = happyGoto action_60 action_225 (68) = happyGoto action_235 action_225 _ = happyReduce_71 action_226 (114) = happyShift action_34 action_226 (36) = happyGoto action_234 action_226 _ = happyFail (happyExpListPerState 226) action_227 (114) = happyShift action_34 action_227 (36) = happyGoto action_233 action_227 _ = happyFail (happyExpListPerState 227) action_228 (112) = happyShift action_190 action_228 _ = happyReduce_57 action_229 _ = happyReduce_51 action_230 _ = happyReduce_47 action_231 _ = happyReduce_44 action_232 _ = happyReduce_40 action_233 _ = happyReduce_61 action_234 _ = happyReduce_60 action_235 _ = happyReduce_64 action_236 (112) = happyShift action_190 action_236 _ = happyReduce_58 action_237 (82) = happyShift action_248 action_237 _ = happyFail (happyExpListPerState 237) action_238 (104) = happyShift action_87 action_238 (106) = happyShift action_88 action_238 (60) = happyGoto action_247 action_238 _ = happyReduce_97 action_239 (74) = happyShift action_72 action_239 (86) = happyShift action_73 action_239 (114) = happyShift action_34 action_239 (115) = happyShift action_74 action_239 (116) = happyShift action_46 action_239 (117) = happyShift action_75 action_239 (118) = happyShift action_63 action_239 (36) = happyGoto action_65 action_239 (37) = happyGoto action_66 action_239 (38) = happyGoto action_67 action_239 (39) = happyGoto action_68 action_239 (40) = happyGoto action_76 action_239 (62) = happyGoto action_246 action_239 (63) = happyGoto action_78 action_239 (64) = happyGoto action_79 action_239 _ = happyFail (happyExpListPerState 239) action_240 (86) = happyShift action_62 action_240 (114) = happyShift action_34 action_240 (118) = happyShift action_63 action_240 (36) = happyGoto action_55 action_240 (40) = happyGoto action_56 action_240 (48) = happyGoto action_57 action_240 (49) = happyGoto action_245 action_240 (50) = happyGoto action_59 action_240 _ = happyReduce_71 action_241 (75) = happyShift action_244 action_241 _ = happyFail (happyExpListPerState 241) action_242 (78) = happyShift action_243 action_242 _ = happyFail (happyExpListPerState 242) action_243 (86) = happyShift action_251 action_243 _ = happyFail (happyExpListPerState 243) action_244 _ = happyReduce_83 action_245 _ = happyReduce_53 action_246 _ = happyReduce_65 action_247 (101) = happyShift action_54 action_247 (69) = happyGoto action_250 action_247 _ = happyReduce_122 action_248 (86) = happyShift action_62 action_248 (114) = happyShift action_34 action_248 (118) = happyShift action_63 action_248 (36) = happyGoto action_55 action_248 (40) = happyGoto action_56 action_248 (48) = happyGoto action_57 action_248 (49) = happyGoto action_249 action_248 (50) = happyGoto action_59 action_248 _ = happyReduce_71 action_249 _ = happyReduce_56 action_250 _ = happyReduce_62 action_251 (115) = happyShift action_74 action_251 (37) = happyGoto action_99 action_251 (55) = happyGoto action_252 action_251 _ = happyReduce_86 action_252 (87) = happyShift action_253 action_252 _ = happyFail (happyExpListPerState 252) action_253 (75) = happyShift action_254 action_253 _ = happyFail (happyExpListPerState 253) action_254 _ = happyReduce_84 happyReduce_33 = happySpecReduce_1 36 happyReduction_33 happyReduction_33 (HappyTerminal (PT _ (TL happy_var_1))) = HappyAbsSyn36 (happy_var_1 ) happyReduction_33 _ = notHappyAtAll happyReduce_34 = happySpecReduce_1 37 happyReduction_34 happyReduction_34 (HappyTerminal (PT _ (TI happy_var_1))) = HappyAbsSyn37 ((read (happy_var_1)) :: Integer ) happyReduction_34 _ = notHappyAtAll happyReduce_35 = happySpecReduce_1 38 happyReduction_35 happyReduction_35 (HappyTerminal (PT _ (TC happy_var_1))) = HappyAbsSyn38 ((read (happy_var_1)) :: Char ) happyReduction_35 _ = notHappyAtAll happyReduce_36 = happySpecReduce_1 39 happyReduction_36 happyReduction_36 (HappyTerminal (PT _ (TD happy_var_1))) = HappyAbsSyn39 ((read (happy_var_1)) :: Double ) happyReduction_36 _ = notHappyAtAll happyReduce_37 = happySpecReduce_1 40 happyReduction_37 happyReduction_37 (HappyTerminal happy_var_1) = HappyAbsSyn40 (AbsBNF.Identifier (mkPosToken happy_var_1) ) happyReduction_37 _ = notHappyAtAll happyReduce_38 = happySpecReduce_1 41 happyReduction_38 happyReduction_38 (HappyAbsSyn43 happy_var_1) = HappyAbsSyn41 (AbsBNF.LGr happy_var_1 ) happyReduction_38 _ = notHappyAtAll happyReduce_39 = happySpecReduce_1 42 happyReduction_39 happyReduction_39 (HappyAbsSyn47 happy_var_1) = HappyAbsSyn42 (AbsBNF.DefAll happy_var_1 ) happyReduction_39 _ = notHappyAtAll happyReduce_40 = happySpecReduce_3 42 happyReduction_40 happyReduction_40 (HappyAbsSyn47 happy_var_3) _ (HappyAbsSyn44 happy_var_1) = HappyAbsSyn42 (AbsBNF.DefSome happy_var_1 happy_var_3 ) happyReduction_40 _ _ _ = notHappyAtAll happyReduce_41 = happySpecReduce_2 42 happyReduction_41 happyReduction_41 (HappyAbsSyn44 happy_var_2) _ = HappyAbsSyn42 (AbsBNF.LDefView happy_var_2 ) happyReduction_41 _ _ = notHappyAtAll happyReduce_42 = happySpecReduce_0 43 happyReduction_42 happyReduction_42 = HappyAbsSyn43 ([] ) happyReduce_43 = happySpecReduce_1 43 happyReduction_43 happyReduction_43 (HappyAbsSyn42 happy_var_1) = HappyAbsSyn43 ((:[]) happy_var_1 ) happyReduction_43 _ = notHappyAtAll happyReduce_44 = happySpecReduce_3 43 happyReduction_44 happyReduction_44 (HappyAbsSyn43 happy_var_3) _ (HappyAbsSyn42 happy_var_1) = HappyAbsSyn43 ((:) happy_var_1 happy_var_3 ) happyReduction_44 _ _ _ = notHappyAtAll happyReduce_45 = happySpecReduce_2 43 happyReduction_45 happyReduction_45 (HappyAbsSyn43 happy_var_2) _ = HappyAbsSyn43 (happy_var_2 ) happyReduction_45 _ _ = notHappyAtAll happyReduce_46 = happySpecReduce_1 44 happyReduction_46 happyReduction_46 (HappyAbsSyn40 happy_var_1) = HappyAbsSyn44 ((:[]) happy_var_1 ) happyReduction_46 _ = notHappyAtAll happyReduce_47 = happySpecReduce_3 44 happyReduction_47 happyReduction_47 (HappyAbsSyn44 happy_var_3) _ (HappyAbsSyn40 happy_var_1) = HappyAbsSyn44 ((:) happy_var_1 happy_var_3 ) happyReduction_47 _ _ _ = notHappyAtAll happyReduce_48 = happySpecReduce_1 45 happyReduction_48 happyReduction_48 (HappyAbsSyn46 happy_var_1) = HappyAbsSyn45 (AbsBNF.Grammar happy_var_1 ) happyReduction_48 _ = notHappyAtAll happyReduce_49 = happySpecReduce_0 46 happyReduction_49 happyReduction_49 = HappyAbsSyn46 ([] ) happyReduce_50 = happySpecReduce_1 46 happyReduction_50 happyReduction_50 (HappyAbsSyn47 happy_var_1) = HappyAbsSyn46 ((:[]) happy_var_1 ) happyReduction_50 _ = notHappyAtAll happyReduce_51 = happySpecReduce_3 46 happyReduction_51 happyReduction_51 (HappyAbsSyn46 happy_var_3) _ (HappyAbsSyn47 happy_var_1) = HappyAbsSyn46 ((:) happy_var_1 happy_var_3 ) happyReduction_51 _ _ _ = notHappyAtAll happyReduce_52 = happySpecReduce_2 46 happyReduction_52 happyReduction_52 (HappyAbsSyn46 happy_var_2) _ = HappyAbsSyn46 (happy_var_2 ) happyReduction_52 _ _ = notHappyAtAll happyReduce_53 = happyReduce 5 47 happyReduction_53 happyReduction_53 ((HappyAbsSyn49 happy_var_5) `HappyStk` _ `HappyStk` (HappyAbsSyn50 happy_var_3) `HappyStk` _ `HappyStk` (HappyAbsSyn51 happy_var_1) `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Rule happy_var_1 happy_var_3 happy_var_5 ) `HappyStk` happyRest happyReduce_54 = happySpecReduce_2 47 happyReduction_54 happyReduction_54 (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Comment happy_var_2 ) happyReduction_54 _ _ = notHappyAtAll happyReduce_55 = happySpecReduce_3 47 happyReduction_55 happyReduction_55 (HappyAbsSyn36 happy_var_3) (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Comments happy_var_2 happy_var_3 ) happyReduction_55 _ _ _ = notHappyAtAll happyReduce_56 = happyReduce 6 47 happyReduction_56 happyReduction_56 ((HappyAbsSyn49 happy_var_6) `HappyStk` _ `HappyStk` (HappyAbsSyn50 happy_var_4) `HappyStk` _ `HappyStk` (HappyAbsSyn51 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Internal happy_var_2 happy_var_4 happy_var_6 ) `HappyStk` happyRest happyReduce_57 = happySpecReduce_3 47 happyReduction_57 happyReduction_57 (HappyAbsSyn70 happy_var_3) (HappyAbsSyn40 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Token happy_var_2 happy_var_3 ) happyReduction_57 _ _ _ = notHappyAtAll happyReduce_58 = happyReduce 4 47 happyReduction_58 happyReduction_58 ((HappyAbsSyn70 happy_var_4) `HappyStk` (HappyAbsSyn40 happy_var_3) `HappyStk` _ `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.PosToken happy_var_3 happy_var_4 ) `HappyStk` happyRest happyReduce_59 = happySpecReduce_2 47 happyReduction_59 happyReduction_59 (HappyAbsSyn44 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Entryp happy_var_2 ) happyReduction_59 _ _ = notHappyAtAll happyReduce_60 = happyReduce 4 47 happyReduction_60 happyReduction_60 ((HappyAbsSyn36 happy_var_4) `HappyStk` (HappyAbsSyn50 happy_var_3) `HappyStk` (HappyAbsSyn69 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Separator happy_var_2 happy_var_3 happy_var_4 ) `HappyStk` happyRest happyReduce_61 = happyReduce 4 47 happyReduction_61 happyReduction_61 ((HappyAbsSyn36 happy_var_4) `HappyStk` (HappyAbsSyn50 happy_var_3) `HappyStk` (HappyAbsSyn69 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Terminator happy_var_2 happy_var_3 happy_var_4 ) `HappyStk` happyRest happyReduce_62 = happyReduce 6 47 happyReduction_62 happyReduction_62 ((HappyAbsSyn69 happy_var_6) `HappyStk` (HappyAbsSyn60 happy_var_5) `HappyStk` (HappyAbsSyn36 happy_var_4) `HappyStk` (HappyAbsSyn36 happy_var_3) `HappyStk` (HappyAbsSyn50 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Delimiters happy_var_2 happy_var_3 happy_var_4 happy_var_5 happy_var_6 ) `HappyStk` happyRest happyReduce_63 = happySpecReduce_3 47 happyReduction_63 happyReduction_63 (HappyAbsSyn37 happy_var_3) (HappyAbsSyn40 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Coercions happy_var_2 happy_var_3 ) happyReduction_63 _ _ _ = notHappyAtAll happyReduce_64 = happyReduce 4 47 happyReduction_64 happyReduction_64 ((HappyAbsSyn68 happy_var_4) `HappyStk` _ `HappyStk` (HappyAbsSyn40 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Rules happy_var_2 happy_var_4 ) `HappyStk` happyRest happyReduce_65 = happyReduce 5 47 happyReduction_65 happyReduction_65 ((HappyAbsSyn62 happy_var_5) `HappyStk` _ `HappyStk` (HappyAbsSyn59 happy_var_3) `HappyStk` (HappyAbsSyn40 happy_var_2) `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn47 (AbsBNF.Function happy_var_2 happy_var_3 happy_var_5 ) `HappyStk` happyRest happyReduce_66 = happySpecReduce_2 47 happyReduction_66 happyReduction_66 (HappyAbsSyn61 happy_var_2) _ = HappyAbsSyn47 (AbsBNF.Layout happy_var_2 ) happyReduction_66 _ _ = notHappyAtAll happyReduce_67 = happySpecReduce_3 47 happyReduction_67 happyReduction_67 (HappyAbsSyn61 happy_var_3) _ _ = HappyAbsSyn47 (AbsBNF.LayoutStop happy_var_3 ) happyReduction_67 _ _ _ = notHappyAtAll happyReduce_68 = happySpecReduce_2 47 happyReduction_68 happyReduction_68 _ _ = HappyAbsSyn47 (AbsBNF.LayoutTop ) happyReduce_69 = happySpecReduce_1 48 happyReduction_69 happyReduction_69 (HappyAbsSyn36 happy_var_1) = HappyAbsSyn48 (AbsBNF.Terminal happy_var_1 ) happyReduction_69 _ = notHappyAtAll happyReduce_70 = happySpecReduce_1 48 happyReduction_70 happyReduction_70 (HappyAbsSyn50 happy_var_1) = HappyAbsSyn48 (AbsBNF.NTerminal happy_var_1 ) happyReduction_70 _ = notHappyAtAll happyReduce_71 = happySpecReduce_0 49 happyReduction_71 happyReduction_71 = HappyAbsSyn49 ([] ) happyReduce_72 = happySpecReduce_2 49 happyReduction_72 happyReduction_72 (HappyAbsSyn49 happy_var_2) (HappyAbsSyn48 happy_var_1) = HappyAbsSyn49 ((:) happy_var_1 happy_var_2 ) happyReduction_72 _ _ = notHappyAtAll happyReduce_73 = happySpecReduce_3 50 happyReduction_73 happyReduction_73 _ (HappyAbsSyn50 happy_var_2) _ = HappyAbsSyn50 (AbsBNF.ListCat happy_var_2 ) happyReduction_73 _ _ _ = notHappyAtAll happyReduce_74 = happySpecReduce_1 50 happyReduction_74 happyReduction_74 (HappyAbsSyn40 happy_var_1) = HappyAbsSyn50 (AbsBNF.IdCat happy_var_1 ) happyReduction_74 _ = notHappyAtAll happyReduce_75 = happySpecReduce_1 51 happyReduction_75 happyReduction_75 (HappyAbsSyn52 happy_var_1) = HappyAbsSyn51 (AbsBNF.LabNoP happy_var_1 ) happyReduction_75 _ = notHappyAtAll happyReduce_76 = happySpecReduce_2 51 happyReduction_76 happyReduction_76 (HappyAbsSyn57 happy_var_2) (HappyAbsSyn52 happy_var_1) = HappyAbsSyn51 (AbsBNF.LabP happy_var_1 happy_var_2 ) happyReduction_76 _ _ = notHappyAtAll happyReduce_77 = happySpecReduce_3 51 happyReduction_77 happyReduction_77 (HappyAbsSyn57 happy_var_3) (HappyAbsSyn52 happy_var_2) (HappyAbsSyn52 happy_var_1) = HappyAbsSyn51 (AbsBNF.LabPF happy_var_1 happy_var_2 happy_var_3 ) happyReduction_77 _ _ _ = notHappyAtAll happyReduce_78 = happySpecReduce_2 51 happyReduction_78 happyReduction_78 (HappyAbsSyn52 happy_var_2) (HappyAbsSyn52 happy_var_1) = HappyAbsSyn51 (AbsBNF.LabF happy_var_1 happy_var_2 ) happyReduction_78 _ _ = notHappyAtAll happyReduce_79 = happySpecReduce_1 52 happyReduction_79 happyReduction_79 (HappyAbsSyn40 happy_var_1) = HappyAbsSyn52 (AbsBNF.Id happy_var_1 ) happyReduction_79 _ = notHappyAtAll happyReduce_80 = happySpecReduce_1 52 happyReduction_80 happyReduction_80 _ = HappyAbsSyn52 (AbsBNF.Wild ) happyReduce_81 = happySpecReduce_2 52 happyReduction_81 happyReduction_81 _ _ = HappyAbsSyn52 (AbsBNF.ListE ) happyReduce_82 = happySpecReduce_3 52 happyReduction_82 happyReduction_82 _ _ _ = HappyAbsSyn52 (AbsBNF.ListCons ) happyReduce_83 = happyReduce 5 52 happyReduction_83 happyReduction_83 (_ `HappyStk` _ `HappyStk` _ `HappyStk` _ `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn52 (AbsBNF.ListOne ) `HappyStk` happyRest happyReduce_84 = happyReduce 9 53 happyReduction_84 happyReduction_84 (_ `HappyStk` _ `HappyStk` (HappyAbsSyn55 happy_var_7) `HappyStk` _ `HappyStk` _ `HappyStk` _ `HappyStk` (HappyAbsSyn56 happy_var_3) `HappyStk` _ `HappyStk` _ `HappyStk` happyRest) = HappyAbsSyn53 (AbsBNF.ProfIt happy_var_3 happy_var_7 ) `HappyStk` happyRest happyReduce_85 = happySpecReduce_3 54 happyReduction_85 happyReduction_85 _ (HappyAbsSyn55 happy_var_2) _ = HappyAbsSyn54 (AbsBNF.Ints happy_var_2 ) happyReduction_85 _ _ _ = notHappyAtAll happyReduce_86 = happySpecReduce_0 55 happyReduction_86 happyReduction_86 = HappyAbsSyn55 ([] ) happyReduce_87 = happySpecReduce_1 55 happyReduction_87 happyReduction_87 (HappyAbsSyn37 happy_var_1) = HappyAbsSyn55 ((:[]) happy_var_1 ) happyReduction_87 _ = notHappyAtAll happyReduce_88 = happySpecReduce_3 55 happyReduction_88 happyReduction_88 (HappyAbsSyn55 happy_var_3) _ (HappyAbsSyn37 happy_var_1) = HappyAbsSyn55 ((:) happy_var_1 happy_var_3 ) happyReduction_88 _ _ _ = notHappyAtAll happyReduce_89 = happySpecReduce_0 56 happyReduction_89 happyReduction_89 = HappyAbsSyn56 ([] ) happyReduce_90 = happySpecReduce_1 56 happyReduction_90 happyReduction_90 (HappyAbsSyn54 happy_var_1) = HappyAbsSyn56 ((:[]) happy_var_1 ) happyReduction_90 _ = notHappyAtAll happyReduce_91 = happySpecReduce_3 56 happyReduction_91 happyReduction_91 (HappyAbsSyn56 happy_var_3) _ (HappyAbsSyn54 happy_var_1) = HappyAbsSyn56 ((:) happy_var_1 happy_var_3 ) happyReduction_91 _ _ _ = notHappyAtAll happyReduce_92 = happySpecReduce_1 57 happyReduction_92 happyReduction_92 (HappyAbsSyn53 happy_var_1) = HappyAbsSyn57 ((:[]) happy_var_1 ) happyReduction_92 _ = notHappyAtAll happyReduce_93 = happySpecReduce_2 57 happyReduction_93 happyReduction_93 (HappyAbsSyn57 happy_var_2) (HappyAbsSyn53 happy_var_1) = HappyAbsSyn57 ((:) happy_var_1 happy_var_2 ) happyReduction_93 _ _ = notHappyAtAll happyReduce_94 = happySpecReduce_1 58 happyReduction_94 happyReduction_94 (HappyAbsSyn40 happy_var_1) = HappyAbsSyn58 (AbsBNF.Arg happy_var_1 ) happyReduction_94 _ = notHappyAtAll happyReduce_95 = happySpecReduce_0 59 happyReduction_95 happyReduction_95 = HappyAbsSyn59 ([] ) happyReduce_96 = happySpecReduce_2 59 happyReduction_96 happyReduction_96 (HappyAbsSyn59 happy_var_2) (HappyAbsSyn58 happy_var_1) = HappyAbsSyn59 ((:) happy_var_1 happy_var_2 ) happyReduction_96 _ _ = notHappyAtAll happyReduce_97 = happySpecReduce_0 60 happyReduction_97 happyReduction_97 = HappyAbsSyn60 (AbsBNF.SepNone ) happyReduce_98 = happySpecReduce_2 60 happyReduction_98 happyReduction_98 (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn60 (AbsBNF.SepTerm happy_var_2 ) happyReduction_98 _ _ = notHappyAtAll happyReduce_99 = happySpecReduce_2 60 happyReduction_99 happyReduction_99 (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn60 (AbsBNF.SepSepar happy_var_2 ) happyReduction_99 _ _ = notHappyAtAll happyReduce_100 = happySpecReduce_1 61 happyReduction_100 happyReduction_100 (HappyAbsSyn36 happy_var_1) = HappyAbsSyn61 ((:[]) happy_var_1 ) happyReduction_100 _ = notHappyAtAll happyReduce_101 = happySpecReduce_3 61 happyReduction_101 happyReduction_101 (HappyAbsSyn61 happy_var_3) _ (HappyAbsSyn36 happy_var_1) = HappyAbsSyn61 ((:) happy_var_1 happy_var_3 ) happyReduction_101 _ _ _ = notHappyAtAll happyReduce_102 = happySpecReduce_3 62 happyReduction_102 happyReduction_102 (HappyAbsSyn62 happy_var_3) _ (HappyAbsSyn62 happy_var_1) = HappyAbsSyn62 (AbsBNF.Cons happy_var_1 happy_var_3 ) happyReduction_102 _ _ _ = notHappyAtAll happyReduce_103 = happySpecReduce_1 62 happyReduction_103 happyReduction_103 (HappyAbsSyn62 happy_var_1) = HappyAbsSyn62 (happy_var_1 ) happyReduction_103 _ = notHappyAtAll happyReduce_104 = happySpecReduce_2 63 happyReduction_104 happyReduction_104 (HappyAbsSyn65 happy_var_2) (HappyAbsSyn40 happy_var_1) = HappyAbsSyn62 (AbsBNF.App happy_var_1 happy_var_2 ) happyReduction_104 _ _ = notHappyAtAll happyReduce_105 = happySpecReduce_1 63 happyReduction_105 happyReduction_105 (HappyAbsSyn62 happy_var_1) = HappyAbsSyn62 (happy_var_1 ) happyReduction_105 _ = notHappyAtAll happyReduce_106 = happySpecReduce_1 64 happyReduction_106 happyReduction_106 (HappyAbsSyn40 happy_var_1) = HappyAbsSyn62 (AbsBNF.Var happy_var_1 ) happyReduction_106 _ = notHappyAtAll happyReduce_107 = happySpecReduce_1 64 happyReduction_107 happyReduction_107 (HappyAbsSyn37 happy_var_1) = HappyAbsSyn62 (AbsBNF.LitInt happy_var_1 ) happyReduction_107 _ = notHappyAtAll happyReduce_108 = happySpecReduce_1 64 happyReduction_108 happyReduction_108 (HappyAbsSyn38 happy_var_1) = HappyAbsSyn62 (AbsBNF.LitChar happy_var_1 ) happyReduction_108 _ = notHappyAtAll happyReduce_109 = happySpecReduce_1 64 happyReduction_109 happyReduction_109 (HappyAbsSyn36 happy_var_1) = HappyAbsSyn62 (AbsBNF.LitString happy_var_1 ) happyReduction_109 _ = notHappyAtAll happyReduce_110 = happySpecReduce_1 64 happyReduction_110 happyReduction_110 (HappyAbsSyn39 happy_var_1) = HappyAbsSyn62 (AbsBNF.LitDouble happy_var_1 ) happyReduction_110 _ = notHappyAtAll happyReduce_111 = happySpecReduce_3 64 happyReduction_111 happyReduction_111 _ (HappyAbsSyn65 happy_var_2) _ = HappyAbsSyn62 (AbsBNF.List happy_var_2 ) happyReduction_111 _ _ _ = notHappyAtAll happyReduce_112 = happySpecReduce_3 64 happyReduction_112 happyReduction_112 _ (HappyAbsSyn62 happy_var_2) _ = HappyAbsSyn62 (happy_var_2 ) happyReduction_112 _ _ _ = notHappyAtAll happyReduce_113 = happySpecReduce_0 65 happyReduction_113 happyReduction_113 = HappyAbsSyn65 ([] ) happyReduce_114 = happySpecReduce_1 65 happyReduction_114 happyReduction_114 (HappyAbsSyn62 happy_var_1) = HappyAbsSyn65 ((:[]) happy_var_1 ) happyReduction_114 _ = notHappyAtAll happyReduce_115 = happySpecReduce_3 65 happyReduction_115 happyReduction_115 (HappyAbsSyn65 happy_var_3) _ (HappyAbsSyn62 happy_var_1) = HappyAbsSyn65 ((:) happy_var_1 happy_var_3 ) happyReduction_115 _ _ _ = notHappyAtAll happyReduce_116 = happySpecReduce_1 66 happyReduction_116 happyReduction_116 (HappyAbsSyn62 happy_var_1) = HappyAbsSyn65 ((:[]) happy_var_1 ) happyReduction_116 _ = notHappyAtAll happyReduce_117 = happySpecReduce_2 66 happyReduction_117 happyReduction_117 (HappyAbsSyn65 happy_var_2) (HappyAbsSyn62 happy_var_1) = HappyAbsSyn65 ((:) happy_var_1 happy_var_2 ) happyReduction_117 _ _ = notHappyAtAll happyReduce_118 = happySpecReduce_1 67 happyReduction_118 happyReduction_118 (HappyAbsSyn49 happy_var_1) = HappyAbsSyn67 (AbsBNF.RHS happy_var_1 ) happyReduction_118 _ = notHappyAtAll happyReduce_119 = happySpecReduce_1 68 happyReduction_119 happyReduction_119 (HappyAbsSyn67 happy_var_1) = HappyAbsSyn68 ((:[]) happy_var_1 ) happyReduction_119 _ = notHappyAtAll happyReduce_120 = happySpecReduce_3 68 happyReduction_120 happyReduction_120 (HappyAbsSyn68 happy_var_3) _ (HappyAbsSyn67 happy_var_1) = HappyAbsSyn68 ((:) happy_var_1 happy_var_3 ) happyReduction_120 _ _ _ = notHappyAtAll happyReduce_121 = happySpecReduce_1 69 happyReduction_121 happyReduction_121 _ = HappyAbsSyn69 (AbsBNF.MNonempty ) happyReduce_122 = happySpecReduce_0 69 happyReduction_122 happyReduction_122 = HappyAbsSyn69 (AbsBNF.MEmpty ) happyReduce_123 = happySpecReduce_3 70 happyReduction_123 happyReduction_123 (HappyAbsSyn70 happy_var_3) _ (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.RAlt happy_var_1 happy_var_3 ) happyReduction_123 _ _ _ = notHappyAtAll happyReduce_124 = happySpecReduce_1 70 happyReduction_124 happyReduction_124 (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (happy_var_1 ) happyReduction_124 _ = notHappyAtAll happyReduce_125 = happySpecReduce_3 71 happyReduction_125 happyReduction_125 (HappyAbsSyn70 happy_var_3) _ (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.RMinus happy_var_1 happy_var_3 ) happyReduction_125 _ _ _ = notHappyAtAll happyReduce_126 = happySpecReduce_1 71 happyReduction_126 happyReduction_126 (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (happy_var_1 ) happyReduction_126 _ = notHappyAtAll happyReduce_127 = happySpecReduce_2 72 happyReduction_127 happyReduction_127 (HappyAbsSyn70 happy_var_2) (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.RSeq happy_var_1 happy_var_2 ) happyReduction_127 _ _ = notHappyAtAll happyReduce_128 = happySpecReduce_1 72 happyReduction_128 happyReduction_128 (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (happy_var_1 ) happyReduction_128 _ = notHappyAtAll happyReduce_129 = happySpecReduce_2 73 happyReduction_129 happyReduction_129 _ (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.RStar happy_var_1 ) happyReduction_129 _ _ = notHappyAtAll happyReduce_130 = happySpecReduce_2 73 happyReduction_130 happyReduction_130 _ (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.RPlus happy_var_1 ) happyReduction_130 _ _ = notHappyAtAll happyReduce_131 = happySpecReduce_2 73 happyReduction_131 happyReduction_131 _ (HappyAbsSyn70 happy_var_1) = HappyAbsSyn70 (AbsBNF.ROpt happy_var_1 ) happyReduction_131 _ _ = notHappyAtAll happyReduce_132 = happySpecReduce_1 73 happyReduction_132 happyReduction_132 _ = HappyAbsSyn70 (AbsBNF.REps ) happyReduce_133 = happySpecReduce_1 73 happyReduction_133 happyReduction_133 (HappyAbsSyn38 happy_var_1) = HappyAbsSyn70 (AbsBNF.RChar happy_var_1 ) happyReduction_133 _ = notHappyAtAll happyReduce_134 = happySpecReduce_3 73 happyReduction_134 happyReduction_134 _ (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn70 (AbsBNF.RAlts happy_var_2 ) happyReduction_134 _ _ _ = notHappyAtAll happyReduce_135 = happySpecReduce_3 73 happyReduction_135 happyReduction_135 _ (HappyAbsSyn36 happy_var_2) _ = HappyAbsSyn70 (AbsBNF.RSeqs happy_var_2 ) happyReduction_135 _ _ _ = notHappyAtAll happyReduce_136 = happySpecReduce_1 73 happyReduction_136 happyReduction_136 _ = HappyAbsSyn70 (AbsBNF.RDigit ) happyReduce_137 = happySpecReduce_1 73 happyReduction_137 happyReduction_137 _ = HappyAbsSyn70 (AbsBNF.RLetter ) happyReduce_138 = happySpecReduce_1 73 happyReduction_138 happyReduction_138 _ = HappyAbsSyn70 (AbsBNF.RUpper ) happyReduce_139 = happySpecReduce_1 73 happyReduction_139 happyReduction_139 _ = HappyAbsSyn70 (AbsBNF.RLower ) happyReduce_140 = happySpecReduce_1 73 happyReduction_140 happyReduction_140 _ = HappyAbsSyn70 (AbsBNF.RAny ) happyReduce_141 = happySpecReduce_3 73 happyReduction_141 happyReduction_141 _ (HappyAbsSyn70 happy_var_2) _ = HappyAbsSyn70 (happy_var_2 ) happyReduction_141 _ _ _ = notHappyAtAll happyNewToken action sts stk [] = action 119 119 notHappyAtAll (HappyState action) sts stk [] happyNewToken action sts stk (tk:tks) = let cont i = action i i tk (HappyState action) sts stk tks in case tk of { PT _ (TS _ 1) -> cont 74; PT _ (TS _ 2) -> cont 75; PT _ (TS _ 3) -> cont 76; PT _ (TS _ 4) -> cont 77; PT _ (TS _ 5) -> cont 78; PT _ (TS _ 6) -> cont 79; PT _ (TS _ 7) -> cont 80; PT _ (TS _ 8) -> cont 81; PT _ (TS _ 9) -> cont 82; PT _ (TS _ 10) -> cont 83; PT _ (TS _ 11) -> cont 84; PT _ (TS _ 12) -> cont 85; PT _ (TS _ 13) -> cont 86; PT _ (TS _ 14) -> cont 87; PT _ (TS _ 15) -> cont 88; PT _ (TS _ 16) -> cont 89; PT _ (TS _ 17) -> cont 90; PT _ (TS _ 18) -> cont 91; PT _ (TS _ 19) -> cont 92; PT _ (TS _ 20) -> cont 93; PT _ (TS _ 21) -> cont 94; PT _ (TS _ 22) -> cont 95; PT _ (TS _ 23) -> cont 96; PT _ (TS _ 24) -> cont 97; PT _ (TS _ 25) -> cont 98; PT _ (TS _ 26) -> cont 99; PT _ (TS _ 27) -> cont 100; PT _ (TS _ 28) -> cont 101; PT _ (TS _ 29) -> cont 102; PT _ (TS _ 30) -> cont 103; PT _ (TS _ 31) -> cont 104; PT _ (TS _ 32) -> cont 105; PT _ (TS _ 33) -> cont 106; PT _ (TS _ 34) -> cont 107; PT _ (TS _ 35) -> cont 108; PT _ (TS _ 36) -> cont 109; PT _ (TS _ 37) -> cont 110; PT _ (TS _ 38) -> cont 111; PT _ (TS _ 39) -> cont 112; PT _ (TS _ 40) -> cont 113; PT _ (TL happy_dollar_dollar) -> cont 114; PT _ (TI happy_dollar_dollar) -> cont 115; PT _ (TC happy_dollar_dollar) -> cont 116; PT _ (TD happy_dollar_dollar) -> cont 117; PT _ (T_Identifier _) -> cont 118; _ -> happyError' ((tk:tks), []) } happyError_ explist 119 tk tks = happyError' (tks, explist) happyError_ explist _ tk tks = happyError' ((tk:tks), explist) happyThen :: () => Either String a -> (a -> Either String b) -> Either String b happyThen = ((>>=)) happyReturn :: () => a -> Either String a happyReturn = (return) happyThen1 m k tks = ((>>=)) m (\a -> k a tks) happyReturn1 :: () => a -> b -> Either String a happyReturn1 = \a tks -> (return) a happyError' :: () => ([(Token)], [Prelude.String]) -> Either String a happyError' = (\(tokens, _) -> happyError tokens) pLGrammar tks = happySomeParser where happySomeParser = happyThen (happyParse action_0 tks) (\x -> case x of {HappyAbsSyn41 z -> happyReturn z; _other -> notHappyAtAll }) pLDef tks = happySomeParser where happySomeParser = happyThen (happyParse action_1 tks) (\x -> case x of {HappyAbsSyn42 z -> happyReturn z; _other -> notHappyAtAll }) pListLDef tks = happySomeParser where happySomeParser = happyThen (happyParse action_2 tks) (\x -> case x of {HappyAbsSyn43 z -> happyReturn z; _other -> notHappyAtAll }) pListIdentifier tks = happySomeParser where happySomeParser = happyThen (happyParse action_3 tks) (\x -> case x of {HappyAbsSyn44 z -> happyReturn z; _other -> notHappyAtAll }) pGrammar tks = happySomeParser where happySomeParser = happyThen (happyParse action_4 tks) (\x -> case x of {HappyAbsSyn45 z -> happyReturn z; _other -> notHappyAtAll }) pListDef tks = happySomeParser where happySomeParser = happyThen (happyParse action_5 tks) (\x -> case x of {HappyAbsSyn46 z -> happyReturn z; _other -> notHappyAtAll }) pDef tks = happySomeParser where happySomeParser = happyThen (happyParse action_6 tks) (\x -> case x of {HappyAbsSyn47 z -> happyReturn z; _other -> notHappyAtAll }) pItem tks = happySomeParser where happySomeParser = happyThen (happyParse action_7 tks) (\x -> case x of {HappyAbsSyn48 z -> happyReturn z; _other -> notHappyAtAll }) pListItem tks = happySomeParser where happySomeParser = happyThen (happyParse action_8 tks) (\x -> case x of {HappyAbsSyn49 z -> happyReturn z; _other -> notHappyAtAll }) pCat tks = happySomeParser where happySomeParser = happyThen (happyParse action_9 tks) (\x -> case x of {HappyAbsSyn50 z -> happyReturn z; _other -> notHappyAtAll }) pLabel tks = happySomeParser where happySomeParser = happyThen (happyParse action_10 tks) (\x -> case x of {HappyAbsSyn51 z -> happyReturn z; _other -> notHappyAtAll }) pLabelId tks = happySomeParser where happySomeParser = happyThen (happyParse action_11 tks) (\x -> case x of {HappyAbsSyn52 z -> happyReturn z; _other -> notHappyAtAll }) pProfItem tks = happySomeParser where happySomeParser = happyThen (happyParse action_12 tks) (\x -> case x of {HappyAbsSyn53 z -> happyReturn z; _other -> notHappyAtAll }) pIntList tks = happySomeParser where happySomeParser = happyThen (happyParse action_13 tks) (\x -> case x of {HappyAbsSyn54 z -> happyReturn z; _other -> notHappyAtAll }) pListInteger tks = happySomeParser where happySomeParser = happyThen (happyParse action_14 tks) (\x -> case x of {HappyAbsSyn55 z -> happyReturn z; _other -> notHappyAtAll }) pListIntList tks = happySomeParser where happySomeParser = happyThen (happyParse action_15 tks) (\x -> case x of {HappyAbsSyn56 z -> happyReturn z; _other -> notHappyAtAll }) pListProfItem tks = happySomeParser where happySomeParser = happyThen (happyParse action_16 tks) (\x -> case x of {HappyAbsSyn57 z -> happyReturn z; _other -> notHappyAtAll }) pArg tks = happySomeParser where happySomeParser = happyThen (happyParse action_17 tks) (\x -> case x of {HappyAbsSyn58 z -> happyReturn z; _other -> notHappyAtAll }) pListArg tks = happySomeParser where happySomeParser = happyThen (happyParse action_18 tks) (\x -> case x of {HappyAbsSyn59 z -> happyReturn z; _other -> notHappyAtAll }) pSeparation tks = happySomeParser where happySomeParser = happyThen (happyParse action_19 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll }) pListString tks = happySomeParser where happySomeParser = happyThen (happyParse action_20 tks) (\x -> case x of {HappyAbsSyn61 z -> happyReturn z; _other -> notHappyAtAll }) pExp tks = happySomeParser where happySomeParser = happyThen (happyParse action_21 tks) (\x -> case x of {HappyAbsSyn62 z -> happyReturn z; _other -> notHappyAtAll }) pExp1 tks = happySomeParser where happySomeParser = happyThen (happyParse action_22 tks) (\x -> case x of {HappyAbsSyn62 z -> happyReturn z; _other -> notHappyAtAll }) pExp2 tks = happySomeParser where happySomeParser = happyThen (happyParse action_23 tks) (\x -> case x of {HappyAbsSyn62 z -> happyReturn z; _other -> notHappyAtAll }) pListExp tks = happySomeParser where happySomeParser = happyThen (happyParse action_24 tks) (\x -> case x of {HappyAbsSyn65 z -> happyReturn z; _other -> notHappyAtAll }) pListExp2 tks = happySomeParser where happySomeParser = happyThen (happyParse action_25 tks) (\x -> case x of {HappyAbsSyn65 z -> happyReturn z; _other -> notHappyAtAll }) pRHS tks = happySomeParser where happySomeParser = happyThen (happyParse action_26 tks) (\x -> case x of {HappyAbsSyn67 z -> happyReturn z; _other -> notHappyAtAll }) pListRHS tks = happySomeParser where happySomeParser = happyThen (happyParse action_27 tks) (\x -> case x of {HappyAbsSyn68 z -> happyReturn z; _other -> notHappyAtAll }) pMinimumSize tks = happySomeParser where happySomeParser = happyThen (happyParse action_28 tks) (\x -> case x of {HappyAbsSyn69 z -> happyReturn z; _other -> notHappyAtAll }) pReg tks = happySomeParser where happySomeParser = happyThen (happyParse action_29 tks) (\x -> case x of {HappyAbsSyn70 z -> happyReturn z; _other -> notHappyAtAll }) pReg1 tks = happySomeParser where happySomeParser = happyThen (happyParse action_30 tks) (\x -> case x of {HappyAbsSyn70 z -> happyReturn z; _other -> notHappyAtAll }) pReg2 tks = happySomeParser where happySomeParser = happyThen (happyParse action_31 tks) (\x -> case x of {HappyAbsSyn70 z -> happyReturn z; _other -> notHappyAtAll }) pReg3 tks = happySomeParser where happySomeParser = happyThen (happyParse action_32 tks) (\x -> case x of {HappyAbsSyn70 z -> happyReturn z; _other -> notHappyAtAll }) happySeq = happyDontSeq happyError :: [Token] -> Either String a happyError ts = Left $ "syntax error at " ++ tokenPos ts ++ case ts of [] -> [] [Err _] -> " due to lexer error" t:_ -> " before `" ++ (prToken t) ++ "'" myLexer = tokens {-# LINE 1 "templates/GenericTemplate.hs" #-} -- $Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp $ data Happy_IntList = HappyCons Prelude.Int Happy_IntList infixr 9 `HappyStk` data HappyStk a = HappyStk a (HappyStk a) ----------------------------------------------------------------------------- -- starting the parse happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll ----------------------------------------------------------------------------- -- Accepting the parse -- If the current token is ERROR_TOK, it means we've just accepted a partial -- parse (a %partial parser). We must ignore the saved token on the top of -- the stack in this case. happyAccept (1) tk st sts (_ `HappyStk` ans `HappyStk` _) = happyReturn1 ans happyAccept j tk st sts (HappyStk ans _) = (happyReturn1 ans) ----------------------------------------------------------------------------- -- Arrays only: do the next action indexShortOffAddr arr off = arr Happy_Data_Array.! off {-# INLINE happyLt #-} happyLt x y = (x Prelude.< y) readArrayBit arr bit = Bits.testBit (indexShortOffAddr arr (bit `Prelude.div` 16)) (bit `Prelude.mod` 16) ----------------------------------------------------------------------------- -- HappyState data type (not arrays) newtype HappyState b c = HappyState (Prelude.Int -> -- token number Prelude.Int -> -- token number (yes, again) b -> -- token semantic value HappyState b c -> -- current state [HappyState b c] -> -- state stack c) ----------------------------------------------------------------------------- -- Shifting a token happyShift new_state (1) tk st sts stk@(x `HappyStk` _) = let i = (case x of { HappyErrorToken (i) -> i }) in -- trace "shifting the error token" $ new_state i i tk (HappyState (new_state)) ((st):(sts)) (stk) happyShift new_state i tk st sts stk = happyNewToken new_state ((st):(sts)) ((HappyTerminal (tk))`HappyStk`stk) -- happyReduce is specialised for the common cases. happySpecReduce_0 i fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happySpecReduce_0 nt fn j tk st@((HappyState (action))) sts stk = action nt j tk st ((st):(sts)) (fn `HappyStk` stk) happySpecReduce_1 i fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happySpecReduce_1 nt fn j tk _ sts@(((st@(HappyState (action))):(_))) (v1`HappyStk`stk') = let r = fn v1 in happySeq r (action nt j tk st sts (r `HappyStk` stk')) happySpecReduce_2 i fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happySpecReduce_2 nt fn j tk _ ((_):(sts@(((st@(HappyState (action))):(_))))) (v1`HappyStk`v2`HappyStk`stk') = let r = fn v1 v2 in happySeq r (action nt j tk st sts (r `HappyStk` stk')) happySpecReduce_3 i fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happySpecReduce_3 nt fn j tk _ ((_):(((_):(sts@(((st@(HappyState (action))):(_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk') = let r = fn v1 v2 v3 in happySeq r (action nt j tk st sts (r `HappyStk` stk')) happyReduce k i fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happyReduce k nt fn j tk st sts stk = case happyDrop (k Prelude.- ((1) :: Prelude.Int)) sts of sts1@(((st1@(HappyState (action))):(_))) -> let r = fn stk in -- it doesn't hurt to always seq here... happyDoSeq r (action nt j tk st1 sts1 r) happyMonadReduce k nt fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happyMonadReduce k nt fn j tk st sts stk = case happyDrop k ((st):(sts)) of sts1@(((st1@(HappyState (action))):(_))) -> let drop_stk = happyDropStk k stk in happyThen1 (fn stk tk) (\r -> action nt j tk st1 sts1 (r `HappyStk` drop_stk)) happyMonad2Reduce k nt fn (1) tk st sts stk = happyFail [] (1) tk st sts stk happyMonad2Reduce k nt fn j tk st sts stk = case happyDrop k ((st):(sts)) of sts1@(((st1@(HappyState (action))):(_))) -> let drop_stk = happyDropStk k stk _ = nt :: Prelude.Int new_state = action in happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk)) happyDrop (0) l = l happyDrop n ((_):(t)) = happyDrop (n Prelude.- ((1) :: Prelude.Int)) t happyDropStk (0) l = l happyDropStk n (x `HappyStk` xs) = happyDropStk (n Prelude.- ((1)::Prelude.Int)) xs ----------------------------------------------------------------------------- -- Moving to a new state after a reduction happyGoto action j tk st = action j j tk (HappyState action) ----------------------------------------------------------------------------- -- Error recovery (ERROR_TOK is the error token) -- parse error if we are in recovery and we fail again happyFail explist (1) tk old_st _ stk@(x `HappyStk` _) = let i = (case x of { HappyErrorToken (i) -> i }) in -- trace "failing" $ happyError_ explist i tk {- We don't need state discarding for our restricted implementation of "error". In fact, it can cause some bogus parses, so I've disabled it for now --SDM -- discard a state happyFail ERROR_TOK tk old_st CONS(HAPPYSTATE(action),sts) (saved_tok `HappyStk` _ `HappyStk` stk) = -- trace ("discarding state, depth " ++ show (length stk)) $ DO_ACTION(action,ERROR_TOK,tk,sts,(saved_tok`HappyStk`stk)) -} -- Enter error recovery: generate an error token, -- save the old token and carry on. happyFail explist i tk (HappyState (action)) sts stk = -- trace "entering error recovery" $ action (1) (1) tk (HappyState (action)) sts ((HappyErrorToken (i)) `HappyStk` stk) -- Internal happy errors: notHappyAtAll :: a notHappyAtAll = Prelude.error "Internal Happy error\n" ----------------------------------------------------------------------------- -- Hack to get the typechecker to accept our action functions ----------------------------------------------------------------------------- -- Seq-ing. If the --strict flag is given, then Happy emits -- happySeq = happyDoSeq -- otherwise it emits -- happySeq = happyDontSeq happyDoSeq, happyDontSeq :: a -> b -> b happyDoSeq a b = a `Prelude.seq` b happyDontSeq a b = b ----------------------------------------------------------------------------- -- Don't inline any functions from the template. GHC has a nasty habit -- of deciding to inline happyGoto everywhere, which increases the size of -- the generated parser quite a bit. {-# NOINLINE happyShift #-} {-# NOINLINE happySpecReduce_0 #-} {-# NOINLINE happySpecReduce_1 #-} {-# NOINLINE happySpecReduce_2 #-} {-# NOINLINE happySpecReduce_3 #-} {-# NOINLINE happyReduce #-} {-# NOINLINE happyMonadReduce #-} {-# NOINLINE happyGoto #-} {-# NOINLINE happyFail #-} -- end of Happy Template.