-- File generated by the BNF Converter. -- Parser definition for use with Happy. { {-# OPTIONS_GHC -fno-warn-incomplete-patterns -fno-warn-overlapping-patterns #-} {-# LANGUAGE PatternSynonyms #-} module ParLBNF ( happyError , myLexer , pGrammar , pListDef , pListItem , pDef , pItem , pCat , pLabel , pLabelId , pProfItem , pIntList , pListInteger , pListIntList , pListProfItem , pListString , pListRHS , pRHS , pMinimumSize , pReg2 , pReg1 , pReg3 , pReg , pListIdent ) where import Prelude import qualified AbsLBNF import LexLBNF } %name pGrammar_internal Grammar %name pListDef_internal ListDef %name pListItem_internal ListItem %name pDef_internal Def %name pItem_internal Item %name pCat_internal Cat %name pLabel_internal Label %name pLabelId_internal LabelId %name pProfItem_internal ProfItem %name pIntList_internal IntList %name pListInteger_internal ListInteger %name pListIntList_internal ListIntList %name pListProfItem_internal ListProfItem %name pListString_internal ListString %name pListRHS_internal ListRHS %name pRHS_internal RHS %name pMinimumSize_internal MinimumSize %name pReg2_internal Reg2 %name pReg1_internal Reg1 %name pReg3_internal Reg3 %name pReg_internal Reg %name pListIdent_internal ListIdent %monad { Err } { (>>=) } { return } %tokentype {Token} %token '(' { PT _ (TS _ 1) } ')' { PT _ (TS _ 2) } '*' { PT _ (TS _ 3) } '+' { PT _ (TS _ 4) } ',' { PT _ (TS _ 5) } '-' { PT _ (TS _ 6) } '.' { PT _ (TS _ 7) } ':' { PT _ (TS _ 8) } '::=' { PT _ (TS _ 9) } ';' { PT _ (TS _ 10) } '?' { PT _ (TS _ 11) } '[' { PT _ (TS _ 12) } ']' { PT _ (TS _ 13) } '_' { PT _ (TS _ 14) } 'char' { PT _ (TS _ 15) } 'coercions' { PT _ (TS _ 16) } 'comment' { PT _ (TS _ 17) } 'digit' { PT _ (TS _ 18) } 'entrypoints' { PT _ (TS _ 19) } 'eps' { PT _ (TS _ 20) } 'internal' { PT _ (TS _ 21) } 'layout' { PT _ (TS _ 22) } 'letter' { PT _ (TS _ 23) } 'lower' { PT _ (TS _ 24) } 'nonempty' { PT _ (TS _ 25) } 'position' { PT _ (TS _ 26) } 'rules' { PT _ (TS _ 27) } 'separator' { PT _ (TS _ 28) } 'stop' { PT _ (TS _ 29) } 'terminator' { PT _ (TS _ 30) } 'token' { PT _ (TS _ 31) } 'toplevel' { PT _ (TS _ 32) } 'upper' { PT _ (TS _ 33) } '{' { PT _ (TS _ 34) } '|' { PT _ (TS _ 35) } '}' { PT _ (TS _ 36) } L_Ident { PT _ (TV _)} L_charac { PT _ (TC _)} L_integ { PT _ (TI _)} L_quoted { PT _ (TL _)} %% Ident :: { (AbsLBNF.BNFC'Position, AbsLBNF.Ident) } Ident : L_Ident { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Ident (tokenText $1)) } Char :: { (AbsLBNF.BNFC'Position, Char) } Char : L_charac { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), (read (tokenText $1) ) :: Char) } Integer :: { (AbsLBNF.BNFC'Position, Integer) } Integer : L_integ { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), (read (tokenText $1) ) :: Integer) } String :: { (AbsLBNF.BNFC'Position, String) } String : L_quoted { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), ((\(PT _ (TL s)) -> s) $1)) } Grammar :: { (AbsLBNF.BNFC'Position, AbsLBNF.Grammar) } Grammar : ListDef { (fst $1, AbsLBNF.MkGrammar (fst $1) (snd $1)) } ListDef :: { (AbsLBNF.BNFC'Position, [AbsLBNF.Def]) } ListDef : {- empty -} { (AbsLBNF.BNFC'NoPosition, []) } | Def ';' ListDef { (fst $1, (:) (snd $1) (snd $3)) } ListItem :: { (AbsLBNF.BNFC'Position, [AbsLBNF.Item]) } ListItem : {- empty -} { (AbsLBNF.BNFC'NoPosition, []) } | Item ListItem { (fst $1, (:) (snd $1) (snd $2)) } Def :: { (AbsLBNF.BNFC'Position, AbsLBNF.Def) } Def : 'coercions' Ident Integer { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Coercions (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $3)) } | 'comment' String { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Comment (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | 'comment' String String { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Comments (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $3)) } | 'entrypoints' ListIdent { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Entryp (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | 'internal' Label '.' Cat '::=' ListItem { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Internal (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $4) (snd $6)) } | 'layout' 'stop' ListString { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.LayoutStop (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $3)) } | 'layout' 'toplevel' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.LayoutTop (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'layout' ListString { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Layout (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | 'position' 'token' Ident Reg { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.PosToken (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $3) (snd $4)) } | 'rules' Ident '::=' ListRHS { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Rules (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $4)) } | 'separator' MinimumSize Cat String { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Separator (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $3) (snd $4)) } | 'terminator' MinimumSize Cat String { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Terminator (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $3) (snd $4)) } | 'token' Ident Reg { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Token (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2) (snd $3)) } | Label '.' Cat '::=' ListItem { (fst $1, AbsLBNF.Rule (fst $1) (snd $1) (snd $3) (snd $5)) } Item :: { (AbsLBNF.BNFC'Position, AbsLBNF.Item) } Item : String { (fst $1, AbsLBNF.Terminal (fst $1) (snd $1)) } | Cat { (fst $1, AbsLBNF.NTerminal (fst $1) (snd $1)) } Cat :: { (AbsLBNF.BNFC'Position, AbsLBNF.Cat) } Cat : '[' Cat ']' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.ListCat (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | Ident { (fst $1, AbsLBNF.IdCat (fst $1) (snd $1)) } Label :: { (AbsLBNF.BNFC'Position, AbsLBNF.Label) } Label : LabelId { (fst $1, AbsLBNF.LabNoP (fst $1) (snd $1)) } | LabelId LabelId { (fst $1, AbsLBNF.LabF (fst $1) (snd $1) (snd $2)) } | LabelId LabelId ListProfItem { (fst $1, AbsLBNF.LabPF (fst $1) (snd $1) (snd $2) (snd $3)) } | LabelId ListProfItem { (fst $1, AbsLBNF.LabP (fst $1) (snd $1) (snd $2)) } LabelId :: { (AbsLBNF.BNFC'Position, AbsLBNF.LabelId) } LabelId : '(' ':' ')' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.ListCons (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | '(' ':' '[' ']' ')' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.ListOne (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | '[' ']' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.ListE (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | '_' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Wild (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | Ident { (fst $1, AbsLBNF.Id (fst $1) (snd $1)) } ProfItem :: { (AbsLBNF.BNFC'Position, AbsLBNF.ProfItem) } ProfItem : '(' '[' ListIntList ']' ',' '[' ListInteger ']' ')' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.ProfIt (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $3) (snd $7)) } IntList :: { (AbsLBNF.BNFC'Position, AbsLBNF.IntList) } IntList : '[' ListInteger ']' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.Ints (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } ListInteger :: { (AbsLBNF.BNFC'Position, [Integer]) } ListInteger : {- empty -} { (AbsLBNF.BNFC'NoPosition, []) } | Integer { (fst $1, (:[]) (snd $1)) } | Integer ',' ListInteger { (fst $1, (:) (snd $1) (snd $3)) } ListIntList :: { (AbsLBNF.BNFC'Position, [AbsLBNF.IntList]) } ListIntList : {- empty -} { (AbsLBNF.BNFC'NoPosition, []) } | IntList { (fst $1, (:[]) (snd $1)) } | IntList ',' ListIntList { (fst $1, (:) (snd $1) (snd $3)) } ListProfItem :: { (AbsLBNF.BNFC'Position, [AbsLBNF.ProfItem]) } ListProfItem : ProfItem { (fst $1, (:[]) (snd $1)) } | ProfItem ListProfItem { (fst $1, (:) (snd $1) (snd $2)) } ListString :: { (AbsLBNF.BNFC'Position, [String]) } ListString : String { (fst $1, (:[]) (snd $1)) } | String ',' ListString { (fst $1, (:) (snd $1) (snd $3)) } ListRHS :: { (AbsLBNF.BNFC'Position, [AbsLBNF.RHS]) } ListRHS : RHS { (fst $1, (:[]) (snd $1)) } | RHS '|' ListRHS { (fst $1, (:) (snd $1) (snd $3)) } RHS :: { (AbsLBNF.BNFC'Position, AbsLBNF.RHS) } RHS : ListItem { (fst $1, AbsLBNF.MkRHS (fst $1) (snd $1)) } MinimumSize :: { (AbsLBNF.BNFC'Position, AbsLBNF.MinimumSize) } MinimumSize : {- empty -} { (AbsLBNF.BNFC'NoPosition, AbsLBNF.MEmpty (AbsLBNF.BNFC'NoPosition)) } | 'nonempty' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.MNonempty (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } Reg2 :: { (AbsLBNF.BNFC'Position, AbsLBNF.Reg) } Reg2 : Reg2 Reg3 { (fst $1, AbsLBNF.RSeq (fst $1) (snd $1) (snd $2)) } | Reg3 { (fst $1, (snd $1)) } Reg1 :: { (AbsLBNF.BNFC'Position, AbsLBNF.Reg) } Reg1 : Reg1 '|' Reg2 { (fst $1, AbsLBNF.RAlt (fst $1) (snd $1) (snd $3)) } | Reg2 { (fst $1, (snd $1)) } | Reg2 '-' Reg2 { (fst $1, AbsLBNF.RMinus (fst $1) (snd $1) (snd $3)) } Reg3 :: { (AbsLBNF.BNFC'Position, AbsLBNF.Reg) } Reg3 : '(' Reg ')' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), (snd $2)) } | '[' String ']' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RAlts (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | 'char' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RAny (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'digit' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RDigit (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'eps' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.REps (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'letter' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RLetter (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'lower' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RLower (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | 'upper' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RUpper (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1))) } | '{' String '}' { (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1), AbsLBNF.RSeqs (uncurry AbsLBNF.BNFC'Position (tokenLineCol $1)) (snd $2)) } | Char { (fst $1, AbsLBNF.RChar (fst $1) (snd $1)) } | Reg3 '*' { (fst $1, AbsLBNF.RStar (fst $1) (snd $1)) } | Reg3 '+' { (fst $1, AbsLBNF.RPlus (fst $1) (snd $1)) } | Reg3 '?' { (fst $1, AbsLBNF.ROpt (fst $1) (snd $1)) } Reg :: { (AbsLBNF.BNFC'Position, AbsLBNF.Reg) } Reg : Reg1 { (fst $1, (snd $1)) } ListIdent :: { (AbsLBNF.BNFC'Position, [AbsLBNF.Ident]) } ListIdent : Ident { (fst $1, (:[]) (snd $1)) } | Ident ',' ListIdent { (fst $1, (:) (snd $1) (snd $3)) } { type Err = Either String happyError :: [Token] -> Err a happyError ts = Left $ "syntax error at " ++ tokenPos ts ++ case ts of [] -> [] [Err _] -> " due to lexer error" t:_ -> " before `" ++ (prToken t) ++ "'" myLexer :: String -> [Token] myLexer = tokens -- Entrypoints pGrammar :: [Token] -> Err AbsLBNF.Grammar pGrammar = fmap snd . pGrammar_internal pListDef :: [Token] -> Err [AbsLBNF.Def] pListDef = fmap snd . pListDef_internal pListItem :: [Token] -> Err [AbsLBNF.Item] pListItem = fmap snd . pListItem_internal pDef :: [Token] -> Err AbsLBNF.Def pDef = fmap snd . pDef_internal pItem :: [Token] -> Err AbsLBNF.Item pItem = fmap snd . pItem_internal pCat :: [Token] -> Err AbsLBNF.Cat pCat = fmap snd . pCat_internal pLabel :: [Token] -> Err AbsLBNF.Label pLabel = fmap snd . pLabel_internal pLabelId :: [Token] -> Err AbsLBNF.LabelId pLabelId = fmap snd . pLabelId_internal pProfItem :: [Token] -> Err AbsLBNF.ProfItem pProfItem = fmap snd . pProfItem_internal pIntList :: [Token] -> Err AbsLBNF.IntList pIntList = fmap snd . pIntList_internal pListInteger :: [Token] -> Err [Integer] pListInteger = fmap snd . pListInteger_internal pListIntList :: [Token] -> Err [AbsLBNF.IntList] pListIntList = fmap snd . pListIntList_internal pListProfItem :: [Token] -> Err [AbsLBNF.ProfItem] pListProfItem = fmap snd . pListProfItem_internal pListString :: [Token] -> Err [String] pListString = fmap snd . pListString_internal pListRHS :: [Token] -> Err [AbsLBNF.RHS] pListRHS = fmap snd . pListRHS_internal pRHS :: [Token] -> Err AbsLBNF.RHS pRHS = fmap snd . pRHS_internal pMinimumSize :: [Token] -> Err AbsLBNF.MinimumSize pMinimumSize = fmap snd . pMinimumSize_internal pReg2 :: [Token] -> Err AbsLBNF.Reg pReg2 = fmap snd . pReg2_internal pReg1 :: [Token] -> Err AbsLBNF.Reg pReg1 = fmap snd . pReg1_internal pReg3 :: [Token] -> Err AbsLBNF.Reg pReg3 = fmap snd . pReg3_internal pReg :: [Token] -> Err AbsLBNF.Reg pReg = fmap snd . pReg_internal pListIdent :: [Token] -> Err [AbsLBNF.Ident] pListIdent = fmap snd . pListIdent_internal }