{-# OPTIONS_GHC -w #-} {-# OPTIONS -fglasgow-exts -cpp #-} {-# LANGUAGE CPP #-} module HERMIT.ParserCore ( parseCore , parseCoreExprT , parse2beforeBiR , parse3beforeBiR , parse4beforeBiR , parse5beforeBiR , Token(..) , parseError , lexer ) where import Control.Arrow import Control.Monad.Reader import Data.Char (isSpace, isDigit) import HERMIT.Context import HERMIT.External import HERMIT.GHC import HERMIT.Kure import HERMIT.Monad import HERMIT.Name import HERMIT.Syntax (isCoreInfixIdChar, isCoreIdFirstChar, isCoreIdChar) import Language.KURE.MonadCatch (prefixFailMsg) import qualified Data.Array as Happy_Data_Array import qualified GHC.Exts as Happy_GHC_Exts -- parser produced by Happy Version 1.19.3 newtype HappyAbsSyn t4 t5 t6 t7 t8 t9 = HappyAbsSyn HappyAny #if __GLASGOW_HASKELL__ >= 607 type HappyAny = Happy_GHC_Exts.Any #else type HappyAny = forall a . a #endif happyIn4 :: t4 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn4 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn4 #-} happyOut4 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t4 happyOut4 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut4 #-} happyIn5 :: t5 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn5 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn5 #-} happyOut5 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t5 happyOut5 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut5 #-} happyIn6 :: t6 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn6 #-} happyOut6 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t6 happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut6 #-} happyIn7 :: t7 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn7 #-} happyOut7 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t7 happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut7 #-} happyIn8 :: t8 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn8 #-} happyOut8 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t8 happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut8 #-} happyIn9 :: t9 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn9 #-} happyOut9 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> t9 happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut9 #-} happyInTok :: (Token) -> (HappyAbsSyn t4 t5 t6 t7 t8 t9) happyInTok x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyInTok #-} happyOutTok :: (HappyAbsSyn t4 t5 t6 t7 t8 t9) -> (Token) happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOutTok #-} happyActOffsets :: HappyAddr happyActOffsets = HappyA# "\xf8\xff\xf8\xff\xf8\xff\x00\x00\x00\x00\x00\x00\x00\x00\xf5\xff\x00\x00\x00\x00\x00\x00\xf0\xff\xf6\xff\x00\x00\x00\x00\x00\x00\x00\x00"# happyGotoOffsets :: HappyAddr happyGotoOffsets = HappyA# "\x0b\x00\x18\x00\x1c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# happyDefActions :: HappyAddr happyDefActions = HappyA# "\x00\x00\x00\x00\xfe\xff\xfc\xff\xf8\xff\xf7\xff\xf9\xff\x00\x00\xf4\xff\xf6\xff\xf5\xff\x00\x00\x00\x00\xfa\xff\xfd\xff\xfb\xff"# happyCheck :: HappyAddr happyCheck = HappyA# "\xff\xff\x0c\x00\x0d\x00\x0d\x00\x0c\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x1c\x00\x22\x00\x1e\x00\x1c\x00\x20\x00\x1e\x00\xff\xff\x20\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x02\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"# happyTable :: HappyAddr happyTable = HappyA# "\x00\x00\x08\x00\x0e\x00\x10\x00\x08\x00\x0c\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x0b\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x09\x00\xff\xff\x0a\x00\x09\x00\x0b\x00\x0a\x00\x00\x00\x0b\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x0e\x00\x04\x00\x05\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# happyReduceArr = Happy_Data_Array.array (1, 11) [ (1 , happyReduce_1), (2 , happyReduce_2), (3 , happyReduce_3), (4 , happyReduce_4), (5 , happyReduce_5), (6 , happyReduce_6), (7 , happyReduce_7), (8 , happyReduce_8), (9 , happyReduce_9), (10 , happyReduce_10), (11 , happyReduce_11) ] happy_n_terms = 35 :: Int happy_n_nonterms = 6 :: Int happyReduce_1 = happySpecReduce_1 0# happyReduction_1 happyReduction_1 happy_x_1 = case happyOut5 happy_x_1 of { happy_var_1 -> happyIn4 (happy_var_1 )} happyReduce_2 = happySpecReduce_2 1# happyReduction_2 happyReduction_2 happy_x_2 happy_x_1 = case happyOut5 happy_x_1 of { happy_var_1 -> case happyOut6 happy_x_2 of { happy_var_2 -> happyIn5 (App happy_var_1 happy_var_2 )}} happyReduce_3 = happySpecReduce_1 1# happyReduction_3 happyReduction_3 happy_x_1 = case happyOut6 happy_x_1 of { happy_var_1 -> happyIn5 (happy_var_1 )} happyReduce_4 = happySpecReduce_3 2# happyReduction_4 happyReduction_4 happy_x_3 happy_x_2 happy_x_1 = case happyOut4 happy_x_2 of { happy_var_2 -> happyIn6 (happy_var_2 )} happyReduce_5 = happyMonadReduce 2# 2# happyReduction_5 happyReduction_5 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen (( lookupName "()") ) (\r -> happyReturn (happyIn6 r)) happyReduce_6 = happySpecReduce_1 2# happyReduction_6 happyReduction_6 happy_x_1 = case happyOut9 happy_x_1 of { happy_var_1 -> happyIn6 (happy_var_1 )} happyReduce_7 = happySpecReduce_1 2# happyReduction_7 happyReduction_7 happy_x_1 = case happyOut7 happy_x_1 of { happy_var_1 -> happyIn6 (happy_var_1 )} happyReduce_8 = happySpecReduce_1 2# happyReduction_8 happyReduction_8 happy_x_1 = case happyOut8 happy_x_1 of { happy_var_1 -> happyIn6 (happy_var_1 )} happyReduce_9 = happyMonadReduce 1# 3# happyReduction_9 happyReduction_9 (happy_x_1 `HappyStk` happyRest) tk = happyThen (case happyOutTok happy_x_1 of { (Tinteger happy_var_1) -> ( mkIntExpr' happy_var_1)} ) (\r -> happyReturn (happyIn7 r)) happyReduce_10 = happyMonadReduce 1# 4# happyReduction_10 happyReduction_10 (happy_x_1 `HappyStk` happyRest) tk = happyThen (case happyOutTok happy_x_1 of { (Tstring happy_var_1) -> ( lift $ mkStringExpr happy_var_1)} ) (\r -> happyReturn (happyIn8 r)) happyReduce_11 = happyMonadReduce 1# 5# happyReduction_11 happyReduction_11 (happy_x_1 `HappyStk` happyRest) tk = happyThen (case happyOutTok happy_x_1 of { (Tname happy_var_1) -> ( lookupName happy_var_1)} ) (\r -> happyReturn (happyIn9 r)) happyNewToken action sts stk [] = happyDoAction 34# notHappyAtAll action sts stk [] happyNewToken action sts stk (tk:tks) = let cont i = happyDoAction i tk action sts stk tks in case tk of { Tforall -> cont 1#; Trec -> cont 2#; Tlet -> cont 3#; Tin -> cont 4#; Tcase -> cont 5#; Tof -> cont 6#; Tcast -> cont 7#; Tnote -> cont 8#; Texternal -> cont 9#; Tlocal -> cont 10#; Twild -> cont 11#; Toparen -> cont 12#; Tcparen -> cont 13#; Tobrace -> cont 14#; Tcbrace -> cont 15#; Thash -> cont 16#; Teq -> cont 17#; Tcolon -> cont 18#; Tcoloncolon -> cont 19#; Tcoloneqcolon -> cont 20#; Tstar -> cont 21#; Tarrow -> cont 22#; Tlambda -> cont 23#; Tat -> cont 24#; Tdot -> cont 25#; Tquestion -> cont 26#; Tsemicolon -> cont 27#; Tname happy_dollar_dollar -> cont 28#; Tcname happy_dollar_dollar -> cont 29#; Tinteger happy_dollar_dollar -> cont 30#; Trational happy_dollar_dollar -> cont 31#; Tstring happy_dollar_dollar -> cont 32#; Tchar happy_dollar_dollar -> cont 33#; _ -> happyError' (tk:tks) } happyError_ 34# tk tks = happyError' tks happyError_ _ tk tks = happyError' (tk:tks) happyThen :: () => CoreParseM a -> (a -> CoreParseM b) -> CoreParseM b happyThen = (>>=) happyReturn :: () => a -> CoreParseM a happyReturn = (return) happyThen1 m k tks = (>>=) m (\a -> k a tks) happyReturn1 :: () => a -> b -> CoreParseM a happyReturn1 = \a tks -> (return) a happyError' :: () => [(Token)] -> CoreParseM a happyError' = parseError parser tks = happySomeParser where happySomeParser = happyThen (happyParse 0# tks) (\x -> happyReturn (happyOut4 x)) happySeq = happyDontSeq mkIntExpr' :: Integer -> CoreParseM CoreExpr #if __GLASGOW_HASKELL__ > 706 mkIntExpr' i = do dflags <- lift getDynFlags return $ mkIntExpr dflags i #else mkIntExpr' i = return $ mkIntExpr i #endif lookupName :: String -> CoreParseM CoreExpr lookupName nm = do c <- ask v <- lift $ prefixFailMsg (nm ++ " lookup: ") $ findId nm c return $ varToCoreExpr v type CoreParseM a = ReaderT HermitC HermitM a parseError :: Monad m => [Token] -> m a parseError ts = fail $ "core parse error: " ++ show ts data Token = Tforall | Trec | Tlet | Tin | Tcase | Tof | Tcast | Tnote | Texternal | Tlocal | Twild -- | Toparen -- | Tcparen -- | Tobrace | Tcbrace | Thash | Teq | Tcolon -- | Tcoloncolon -- | Tcoloneqcolon | Tstar | Tarrow | Tdoublearrow | Tlambda -- | Tat | Tdot | Tquestion | Tsemicolon | Tname String | Tcname String | Tinteger Integer | Trational Float | Tstring String | Tchar Char deriving (Eq, Show) lexer :: String -> Either String [Token] lexer [] = Right [] lexer ('_' :cs) = fmap (Twild:) $ lexer cs lexer ('(' :cs) = fmap (Toparen:) $ lexer cs lexer (')' :cs) = fmap (Tcparen:) $ lexer cs lexer (':':':':cs) = fmap (Tcoloncolon:) $ lexer cs -- lexer (':' :cs) = fmap (Tcolon:) $ lexer cs lexer ('\\':cs) = fmap (Tlambda:) $ lexer cs lexer ('-':'>':cs) = fmap (Tarrow:) $ lexer cs lexer ('=':'>':cs) = fmap (Tdoublearrow:) $ lexer cs lexer ('\"':cs) = let (str,rest) = span (/='\"') cs in case rest of ('\"':cs') -> fmap (Tstring str:) $ lexer cs' _ -> Left "lexer: no matching quote" lexer s@(c:cs) | isSpace c = lexer cs | isDigit c = let (i,s') = span isDigit s in fmap (Tinteger (read i):) $ lexer s' | isCoreIdFirstChar c = let (i,s') = span isCoreIdChar s in fmap (Tname i:) $ lexer s' | isCoreInfixIdChar c = let (op,s') = span isCoreInfixIdChar s in fmap (Tname op:) $ lexer s' lexer s = Left $ "lexer: no match on " ++ s --------------------------------------------- parseCore :: CoreString -> HermitC -> HermitM CoreExpr parseCore (CoreString s) c = case lexer s of Left msg -> fail msg Right tokens -> runReaderT (parser tokens) c --------------------------------------------- -- These should probably go somewhere else. -- | Parse a 'CoreString' to a 'CoreExpr', using the current context. parseCoreExprT :: CoreString -> TransformH a CoreExpr parseCoreExprT = contextonlyT . parseCore parse2beforeBiR :: (CoreExpr -> CoreExpr -> BiRewriteH a) -> CoreString -> CoreString -> BiRewriteH a parse2beforeBiR f s1 s2 = beforeBiR (parseCoreExprT s1 &&& parseCoreExprT s2) (uncurry f) parse3beforeBiR :: (CoreExpr -> CoreExpr -> CoreExpr -> BiRewriteH a) -> CoreString -> CoreString -> CoreString -> BiRewriteH a parse3beforeBiR f s1 s2 s3 = beforeBiR ((parseCoreExprT s1 &&& parseCoreExprT s2) &&& parseCoreExprT s3) ((uncurry.uncurry) f) parse4beforeBiR :: (CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr -> BiRewriteH a) -> CoreString -> CoreString -> CoreString -> CoreString -> BiRewriteH a parse4beforeBiR f s1 s2 s3 s4 = beforeBiR (((parseCoreExprT s1 &&& parseCoreExprT s2) &&& parseCoreExprT s3) &&& parseCoreExprT s4) ((uncurry.uncurry.uncurry) f) parse5beforeBiR :: (CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr -> BiRewriteH a) -> CoreString -> CoreString -> CoreString -> CoreString -> CoreString -> BiRewriteH a parse5beforeBiR f s1 s2 s3 s4 s5 = beforeBiR ((((parseCoreExprT s1 &&& parseCoreExprT s2) &&& parseCoreExprT s3) &&& parseCoreExprT s4) &&& parseCoreExprT s5) ((uncurry.uncurry.uncurry.uncurry) f) --------------------------------------------- {-# LINE 1 "templates/GenericTemplate.hs" #-} {-# LINE 1 "templates/GenericTemplate.hs" #-} {-# LINE 1 "" #-} {-# LINE 1 "templates/GenericTemplate.hs" #-} -- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp {-# LINE 13 "templates/GenericTemplate.hs" #-} -- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex. #if __GLASGOW_HASKELL__ > 706 #define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Bool) #define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Bool) #define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Bool) #else #define LT(n,m) (n Happy_GHC_Exts.<# m) #define GTE(n,m) (n Happy_GHC_Exts.>=# m) #define EQ(n,m) (n Happy_GHC_Exts.==# m) #endif {-# LINE 46 "templates/GenericTemplate.hs" #-} data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList {-# LINE 67 "templates/GenericTemplate.hs" #-} {-# LINE 77 "templates/GenericTemplate.hs" #-} 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 0#, 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 0# tk st sts (_ `HappyStk` ans `HappyStk` _) = happyReturn1 ans happyAccept j tk st sts (HappyStk ans _) = (happyTcHack j (happyTcHack st)) (happyReturn1 ans) ----------------------------------------------------------------------------- -- Arrays only: do the next action happyDoAction i tk st = {- nothing -} case action of 0# -> {- nothing -} happyFail i tk st -1# -> {- nothing -} happyAccept i tk st n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -} (happyReduceArr Happy_Data_Array.! rule) i tk st where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#)))))) n -> {- nothing -} happyShift new_state i tk st where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) where off = indexShortOffAddr happyActOffsets st off_i = (off Happy_GHC_Exts.+# i) check = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#)) then EQ(indexShortOffAddr happyCheck off_i, i) else False action | check = indexShortOffAddr happyTable off_i | otherwise = indexShortOffAddr happyDefActions st indexShortOffAddr (HappyA# arr) off = Happy_GHC_Exts.narrow16Int# i where i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low) high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#))) low = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off')) off' = off Happy_GHC_Exts.*# 2# data HappyAddr = HappyA# Happy_GHC_Exts.Addr# ----------------------------------------------------------------------------- -- HappyState data type (not arrays) {-# LINE 170 "templates/GenericTemplate.hs" #-} ----------------------------------------------------------------------------- -- Shifting a token happyShift new_state 0# tk st sts stk@(x `HappyStk` _) = let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in -- trace "shifting the error token" $ happyDoAction i tk new_state (HappyCons (st) (sts)) (stk) happyShift new_state i tk st sts stk = happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk) -- happyReduce is specialised for the common cases. happySpecReduce_0 i fn 0# tk st sts stk = happyFail 0# tk st sts stk happySpecReduce_0 nt fn j tk st@((action)) sts stk = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk) happySpecReduce_1 i fn 0# tk st sts stk = happyFail 0# tk st sts stk happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk') = let r = fn v1 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happySpecReduce_2 i fn 0# tk st sts stk = happyFail 0# tk st sts stk happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk') = let r = fn v1 v2 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happySpecReduce_3 i fn 0# tk st sts stk = happyFail 0# tk st sts stk happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk') = let r = fn v1 v2 v3 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happyReduce k i fn 0# tk st sts stk = happyFail 0# tk st sts stk happyReduce k nt fn j tk st sts stk = case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of sts1@((HappyCons (st1@(action)) (_))) -> let r = fn stk in -- it doesn't hurt to always seq here... happyDoSeq r (happyGoto nt j tk st1 sts1 r) happyMonadReduce k nt fn 0# tk st sts stk = happyFail 0# tk st sts stk happyMonadReduce k nt fn j tk st sts stk = case happyDrop k (HappyCons (st) (sts)) of sts1@((HappyCons (st1@(action)) (_))) -> let drop_stk = happyDropStk k stk in happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk)) happyMonad2Reduce k nt fn 0# tk st sts stk = happyFail 0# tk st sts stk happyMonad2Reduce k nt fn j tk st sts stk = case happyDrop k (HappyCons (st) (sts)) of sts1@((HappyCons (st1@(action)) (_))) -> let drop_stk = happyDropStk k stk off = indexShortOffAddr happyGotoOffsets st1 off_i = (off Happy_GHC_Exts.+# nt) new_state = indexShortOffAddr happyTable off_i in happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk)) happyDrop 0# l = l happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t happyDropStk 0# l = l happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs ----------------------------------------------------------------------------- -- Moving to a new state after a reduction happyGoto nt j tk st = {- nothing -} happyDoAction j tk new_state where off = indexShortOffAddr happyGotoOffsets st off_i = (off Happy_GHC_Exts.+# nt) new_state = indexShortOffAddr happyTable off_i ----------------------------------------------------------------------------- -- Error recovery (0# is the error token) -- parse error if we are in recovery and we fail again happyFail 0# tk old_st _ stk@(x `HappyStk` _) = let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in -- trace "failing" $ happyError_ 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 0# tk old_st (HappyCons ((action)) (sts)) (saved_tok `HappyStk` _ `HappyStk` stk) = -- trace ("discarding state, depth " ++ show (length stk)) $ happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk)) -} -- Enter error recovery: generate an error token, -- save the old token and carry on. happyFail i tk (action) sts stk = -- trace "entering error recovery" $ happyDoAction 0# tk action sts ( (Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk) -- Internal happy errors: notHappyAtAll :: a notHappyAtAll = error "Internal Happy error\n" ----------------------------------------------------------------------------- -- Hack to get the typechecker to accept our action functions happyTcHack :: Happy_GHC_Exts.Int# -> a -> a happyTcHack x y = y {-# INLINE happyTcHack #-} ----------------------------------------------------------------------------- -- 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 `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 happyDoAction #-} {-# NOINLINE happyTable #-} {-# NOINLINE happyCheck #-} {-# NOINLINE happyActOffsets #-} {-# NOINLINE happyGotoOffsets #-} {-# NOINLINE happyDefActions #-} {-# 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.