-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A compiler front-end generator. -- -- The BNF Converter is a compiler construction tool generating a -- compiler front-end from a Labelled BNF grammar. It was originally -- written to generate Haskell code, but can also be used for generating -- Agda, C, C++, Java, Ocaml and XML code. -- -- Given a Labelled BNF grammar the tool produces: an abstract syntax as -- a Haskell, Agda, C, C++, Ocaml module or Java directory, a case -- skeleton for the abstract syntax in the same language, an Alex, JLex, -- or Flex lexer generator file, a Happy, CUP, Bison, or Antlr parser -- generator file, a pretty-printer as a Haskell, Agda, C, C++, Java, or -- Ocaml module, an XML representation, a LaTeX file containing a -- readable specification of the language. @package BNFC @version 2.9.4.1 -- | The abstract syntax of language BNFC. module BNFC.Abs data Grammar Grammar :: [Def] -> Grammar data Def Rule :: Label -> Cat -> [Item] -> Def Comment :: String -> Def Comments :: String -> String -> Def Internal :: Label -> Cat -> [Item] -> Def Token :: Identifier -> Reg -> Def PosToken :: Identifier -> Reg -> Def Entryp :: [Cat] -> Def Separator :: MinimumSize -> Cat -> String -> Def Terminator :: MinimumSize -> Cat -> String -> Def Delimiters :: Cat -> String -> String -> Separation -> MinimumSize -> Def Coercions :: Identifier -> Integer -> Def Rules :: Identifier -> [RHS] -> Def Function :: Identifier -> [Arg] -> Exp -> Def Layout :: [String] -> Def LayoutStop :: [String] -> Def LayoutTop :: Def data Item Terminal :: String -> Item NTerminal :: Cat -> Item data Cat ListCat :: Cat -> Cat IdCat :: Identifier -> Cat data Label Id :: Identifier -> Label Wild :: Label ListE :: Label ListCons :: Label ListOne :: Label data Arg Arg :: Identifier -> Arg data Separation SepNone :: Separation SepTerm :: String -> Separation SepSepar :: String -> Separation data Exp Cons :: Exp -> Exp -> Exp App :: Identifier -> [Exp] -> Exp Var :: Identifier -> Exp LitInt :: Integer -> Exp LitChar :: Char -> Exp LitString :: String -> Exp LitDouble :: Double -> Exp List :: [Exp] -> Exp data RHS RHS :: [Item] -> RHS data MinimumSize MNonempty :: MinimumSize MEmpty :: MinimumSize data Reg RAlt :: Reg -> Reg -> Reg RMinus :: Reg -> Reg -> Reg RSeq :: Reg -> Reg -> Reg RStar :: Reg -> Reg RPlus :: Reg -> Reg ROpt :: Reg -> Reg REps :: Reg RChar :: Char -> Reg RAlts :: String -> Reg RSeqs :: String -> Reg RDigit :: Reg RLetter :: Reg RUpper :: Reg RLower :: Reg RAny :: Reg newtype Identifier Identifier :: ((Int, Int), String) -> Identifier -- | Start position (line, column) of something. type BNFC'Position = Maybe (Int, Int) pattern BNFC'NoPosition :: BNFC'Position pattern BNFC'Position :: Int -> Int -> BNFC'Position -- | Get the start position of something. class HasPosition a hasPosition :: HasPosition a => a -> BNFC'Position instance GHC.Read.Read BNFC.Abs.Separation instance GHC.Show.Show BNFC.Abs.Separation instance GHC.Classes.Ord BNFC.Abs.Separation instance GHC.Classes.Eq BNFC.Abs.Separation instance GHC.Read.Read BNFC.Abs.MinimumSize instance GHC.Show.Show BNFC.Abs.MinimumSize instance GHC.Classes.Ord BNFC.Abs.MinimumSize instance GHC.Classes.Eq BNFC.Abs.MinimumSize instance GHC.Read.Read BNFC.Abs.Reg instance GHC.Show.Show BNFC.Abs.Reg instance GHC.Classes.Ord BNFC.Abs.Reg instance GHC.Classes.Eq BNFC.Abs.Reg instance GHC.Read.Read BNFC.Abs.Identifier instance GHC.Show.Show BNFC.Abs.Identifier instance GHC.Classes.Ord BNFC.Abs.Identifier instance GHC.Classes.Eq BNFC.Abs.Identifier instance GHC.Read.Read BNFC.Abs.Exp instance GHC.Show.Show BNFC.Abs.Exp instance GHC.Classes.Ord BNFC.Abs.Exp instance GHC.Classes.Eq BNFC.Abs.Exp instance GHC.Read.Read BNFC.Abs.Arg instance GHC.Show.Show BNFC.Abs.Arg instance GHC.Classes.Ord BNFC.Abs.Arg instance GHC.Classes.Eq BNFC.Abs.Arg instance GHC.Read.Read BNFC.Abs.Label instance GHC.Show.Show BNFC.Abs.Label instance GHC.Classes.Ord BNFC.Abs.Label instance GHC.Classes.Eq BNFC.Abs.Label instance GHC.Read.Read BNFC.Abs.Cat instance GHC.Show.Show BNFC.Abs.Cat instance GHC.Classes.Ord BNFC.Abs.Cat instance GHC.Classes.Eq BNFC.Abs.Cat instance GHC.Read.Read BNFC.Abs.Item instance GHC.Show.Show BNFC.Abs.Item instance GHC.Classes.Ord BNFC.Abs.Item instance GHC.Classes.Eq BNFC.Abs.Item instance GHC.Read.Read BNFC.Abs.RHS instance GHC.Show.Show BNFC.Abs.RHS instance GHC.Classes.Ord BNFC.Abs.RHS instance GHC.Classes.Eq BNFC.Abs.RHS instance GHC.Read.Read BNFC.Abs.Def instance GHC.Show.Show BNFC.Abs.Def instance GHC.Classes.Ord BNFC.Abs.Def instance GHC.Classes.Eq BNFC.Abs.Def instance GHC.Read.Read BNFC.Abs.Grammar instance GHC.Show.Show BNFC.Abs.Grammar instance GHC.Classes.Ord BNFC.Abs.Grammar instance GHC.Classes.Eq BNFC.Abs.Grammar instance BNFC.Abs.HasPosition BNFC.Abs.Identifier -- | Common definitions for the modules of the C backend. module BNFC.Backend.C.Common -- | Switch C to language variant that has strdup. posixC :: [String] module BNFC.Backend.CPP.STL.STLUtils nsDefine :: Maybe String -> String -> String nsStart :: Maybe String -> String nsEnd :: Maybe String -> String nsScope :: Maybe String -> String nsString :: Maybe String -> String module BNFC.Backend.Common.StrUtils -- | Function that, given an input string, renders it either as a char (if -- it has legth 1) or a string. It should also excape characters -- correctly. The first returned value is the 'type' of the string: -- either C for char or S for string. (used in the C printer to choose -- the right rendering function) e.g. >>> renderCharOrString "a" -- (C,"a") >>> renderCharOrString "abc" -- (S,""abc"") >>> renderCharOrString "'" -- (C,"\\'") >>> renderCharOrString ""\'" -- (S,""\"\\\'"") renderCharOrString :: String -> (Char, String) -- | Helper function that escapes characters in strings >>> -- escapeChars "\" "\\" >>> escapeChars """ "\"" >>> -- escapeChars "'" "\'" escapeChars :: String -> String module BNFC.Backend.Java.RegToAntlrLexer printRegJLex :: Reg -> String -- | Escape character for use inside single quotes. escapeCharInSingleQuotes :: Char -> String instance BNFC.Backend.Java.RegToAntlrLexer.Print BNFC.Abs.Identifier instance BNFC.Backend.Java.RegToAntlrLexer.Print BNFC.Abs.Reg module BNFC.Lex alex_tab_size :: Int alex_base :: AlexAddr alex_table :: AlexAddr alex_check :: AlexAddr alex_deflt :: AlexAddr alex_accept :: Array Int (AlexAcc user) alex_actions :: Array Int (Posn -> String -> Token) data AlexAddr AlexA# :: Addr# -> AlexAddr alexIndexInt16OffAddr :: AlexAddr -> Int# -> Int# alexIndexInt32OffAddr :: AlexAddr -> Int# -> Int# quickIndex :: Array Int (AlexAcc (Any :: Type)) -> Int -> AlexAcc (Any :: Type) data AlexReturn a AlexEOF :: AlexReturn a AlexError :: !AlexInput -> AlexReturn a AlexSkip :: !AlexInput -> !Int -> AlexReturn a AlexToken :: !AlexInput -> !Int -> a -> AlexReturn a alexScan :: (Posn, Char, [Byte], String) -> Int -> AlexReturn (Posn -> String -> Token) alexScanUser :: t -> (Posn, Char, [Byte], String) -> Int -> AlexReturn (Posn -> String -> Token) alex_scan_tkn :: t1 -> t2 -> Int# -> AlexInput -> Int# -> AlexLastAcc -> (AlexLastAcc, (Posn, Char, [Byte], String)) data AlexLastAcc AlexNone :: AlexLastAcc AlexLastAcc :: !Int -> !AlexInput -> !Int -> AlexLastAcc AlexLastSkip :: !AlexInput -> !Int -> AlexLastAcc data AlexAcc user AlexAccNone :: AlexAcc user AlexAcc :: Int -> AlexAcc user AlexAccSkip :: AlexAcc user -- | Create a token with position. tok :: (String -> Tok) -> Posn -> String -> Token -- | Token without position. data Tok -- | Reserved word or symbol. TK :: {-# UNPACK #-} !TokSymbol -> Tok -- | String literal. TL :: !String -> Tok -- | Integer literal. TI :: !String -> Tok -- | Identifier. TV :: !String -> Tok -- | Float literal. TD :: !String -> Tok -- | Character literal. TC :: !String -> Tok T_Identifier :: !String -> Tok -- | Smart constructor for Tok for the sake of backwards -- compatibility. pattern TS :: String -> Int -> Tok -- | Keyword or symbol tokens have a unique ID. data TokSymbol TokSymbol :: String -> !Int -> TokSymbol -- | Keyword or symbol text. [tsText] :: TokSymbol -> String -- | Unique ID. [tsID] :: TokSymbol -> !Int -- | Token with position. data Token PT :: Posn -> Tok -> Token Err :: Posn -> Token -- | Pretty print a position. printPosn :: Posn -> String -- | Pretty print the position of the first token in the list. tokenPos :: [Token] -> String -- | Get the position of a token. tokenPosn :: Token -> Posn -- | Get line and column of a token. tokenLineCol :: Token -> (Int, Int) -- | Get line and column of a position. posLineCol :: Posn -> (Int, Int) -- | Convert a token into "position token" form. mkPosToken :: Token -> ((Int, Int), String) -- | Convert a token to its text. tokenText :: Token -> String -- | Convert a token to a string. prToken :: Token -> String -- | Finite map from text to token organized as binary search tree. data BTree -- | Nil (leaf). N :: BTree -- | Binary node. B :: String -> Tok -> BTree -> BTree -> BTree -- | Convert potential keyword into token or use fallback conversion. eitherResIdent :: (String -> Tok) -> String -> Tok -- | The keywords and symbols of the language organized as binary search -- tree. resWords :: BTree -- | Unquote string literal. unescapeInitTail :: String -> String data Posn Pn :: !Int -> !Int -> !Int -> Posn alexStartPos :: Posn alexMove :: Posn -> Char -> Posn type Byte = Word8 type AlexInput = (Posn, Char, [Byte], String) tokens :: String -> [Token] alexGetByte :: AlexInput -> Maybe (Byte, AlexInput) alexInputPrevChar :: AlexInput -> Char -- | Encode a Haskell String to a list of Word8 values, in UTF8 format. utf8Encode :: Char -> [Word8] alex_action_3 :: Posn -> String -> Token alex_action_4 :: Posn -> String -> Token alex_action_5 :: Posn -> String -> Token alex_action_6 :: Posn -> String -> Token alex_action_7 :: Posn -> String -> Token alex_action_8 :: Posn -> String -> Token alex_action_9 :: Posn -> String -> Token instance GHC.Show.Show BNFC.Lex.TokSymbol instance GHC.Classes.Ord BNFC.Lex.Tok instance GHC.Show.Show BNFC.Lex.Tok instance GHC.Classes.Eq BNFC.Lex.Tok instance GHC.Show.Show BNFC.Lex.BTree instance GHC.Classes.Ord BNFC.Lex.Posn instance GHC.Show.Show BNFC.Lex.Posn instance GHC.Classes.Eq BNFC.Lex.Posn instance GHC.Classes.Ord BNFC.Lex.Token instance GHC.Show.Show BNFC.Lex.Token instance GHC.Classes.Eq BNFC.Lex.Token instance GHC.Classes.Eq BNFC.Lex.TokSymbol instance GHC.Classes.Ord BNFC.Lex.TokSymbol module BNFC.License license :: String module BNFC.Par happyError :: [Token] -> Err a myLexer :: String -> [Token] pGrammar :: [Token] -> Err Grammar pListDef :: [Token] -> Err [Def] pDef :: [Token] -> Err Def pItem :: [Token] -> Err Item pListItem :: [Token] -> Err [Item] pCat :: [Token] -> Err Cat pListCat :: [Token] -> Err [Cat] pLabel :: [Token] -> Err Label pArg :: [Token] -> Err Arg pListArg :: [Token] -> Err [Arg] pSeparation :: [Token] -> Err Separation pListString :: [Token] -> Err [String] pExp :: [Token] -> Err Exp pExp1 :: [Token] -> Err Exp pExp2 :: [Token] -> Err Exp pListExp :: [Token] -> Err [Exp] pListExp2 :: [Token] -> Err [Exp] pRHS :: [Token] -> Err RHS pListRHS :: [Token] -> Err [RHS] pMinimumSize :: [Token] -> Err MinimumSize pReg :: [Token] -> Err Reg pReg1 :: [Token] -> Err Reg pReg2 :: [Token] -> Err Reg pReg3 :: [Token] -> Err Reg -- | Extends 'PrettyPrint'. module BNFC.PrettyPrint -- | Overloaded function pretty. class Pretty a pretty :: Pretty a => a -> Doc prettyPrec :: Pretty a => Int -> a -> Doc -- | Render as String. prettyShow :: Pretty a => a -> String -- | Put parens around document if given condition is true. -- --
--   >>> parensIf True "foo"
--   (foo)
--   
-- --
--   >>> parensIf False "bar"
--   bar
--   
parensIf :: Bool -> Doc -> Doc -- | Separate vertically by a blank line. -- --
--   >>> "foo" $++$ "bar"
--   foo
--   
--   bar
--   
-- --
--   >>> "foo" $++$ empty
--   foo
--   
($++$) :: Doc -> Doc -> Doc -- | List version of $++$. -- --
--   >>> vsep [ "foo", nest 4 "bar" ]
--   foo
--   
--       bar
--   
-- --
--   >>> vsep []
--   
vsep :: [Doc] -> Doc -- | List version of $+$. -- --
--   >>> vcat' [text "abc", nest 4 (text "def")]
--   abc
--       def
--   
vcat' :: [Doc] -> Doc -- | Pretty print separator with = (for assignments...). -- --
--   >>> "a" <=> "123"
--   a = 123
--   
(<=>) :: Doc -> Doc -> Doc -- | Print a list of 0-1 elements on the same line as some preamble and -- from 2 elements on the following lines, indented. -- --
--   >>> prettyList 2 ("foo" <+> equals) lbrack rbrack comma []
--   foo = []
--   
--   >>> prettyList 2 ("foo" <+> equals) lbrack rbrack comma [ "a" ]
--   foo = [a]
--   
--   >>> prettyList 2 ("foo" <+> equals) lbrack rbrack comma [ "a", "b" ]
--   foo =
--     [ a
--     , b
--     ]
--   
-- -- Used in the Agda backend. prettyList :: Int -> Doc -> Doc -> Doc -> Doc -> [Doc] -> Doc -- | Code block. A block of C/Java code, surrounded by {} and indented. -- --
--   >>> codeblock 4 ["abc", "def"]
--   {
--       abc
--       def
--   }
--   
-- -- Used in the C backend. codeblock :: Int -> [Doc] -> Doc instance BNFC.PrettyPrint.Pretty GHC.Types.Int instance BNFC.PrettyPrint.Pretty GHC.Integer.Type.Integer instance BNFC.PrettyPrint.Pretty GHC.Base.String module BNFC.Backend.Haskell.MkErrM mkErrM :: String -> Doc -- | Pretty-printer for BNFC. module BNFC.Print -- | The top-level printing method. printTree :: Print a => a -> String type Doc = [ShowS] -> [ShowS] doc :: ShowS -> Doc render :: Doc -> String parenth :: Doc -> Doc concatS :: [ShowS] -> ShowS concatD :: [Doc] -> Doc replicateS :: Int -> ShowS -> ShowS -- | The printer class does the job. class Print a prt :: Print a => Int -> a -> Doc printString :: String -> Doc mkEsc :: Char -> Char -> ShowS prPrec :: Int -> Int -> Doc -> Doc instance BNFC.Print.Print a => BNFC.Print.Print [a] instance BNFC.Print.Print GHC.Types.Char instance BNFC.Print.Print GHC.Base.String instance BNFC.Print.Print GHC.Integer.Type.Integer instance BNFC.Print.Print GHC.Types.Double instance BNFC.Print.Print BNFC.Abs.Identifier instance BNFC.Print.Print BNFC.Abs.Grammar instance BNFC.Print.Print [BNFC.Abs.Def] instance BNFC.Print.Print BNFC.Abs.Def instance BNFC.Print.Print BNFC.Abs.Item instance BNFC.Print.Print [BNFC.Abs.Item] instance BNFC.Print.Print BNFC.Abs.Cat instance BNFC.Print.Print [BNFC.Abs.Cat] instance BNFC.Print.Print BNFC.Abs.Label instance BNFC.Print.Print BNFC.Abs.Arg instance BNFC.Print.Print [BNFC.Abs.Arg] instance BNFC.Print.Print BNFC.Abs.Separation instance BNFC.Print.Print [GHC.Base.String] instance BNFC.Print.Print BNFC.Abs.Exp instance BNFC.Print.Print [BNFC.Abs.Exp] instance BNFC.Print.Print BNFC.Abs.RHS instance BNFC.Print.Print [BNFC.Abs.RHS] instance BNFC.Print.Print BNFC.Abs.MinimumSize instance BNFC.Print.Print BNFC.Abs.Reg -- | Tools to manipulate regular expressions. module BNFC.Regex -- | Check if a regular expression is nullable (accepts the empty string) nullable :: Reg -> Bool -- | Simplification of regular expression, mostly for the purpose of -- simplifying character alternatives (character classes). -- -- This may help lexer backends, since often lexer generators have a -- limited syntax for character classes. simpReg :: Reg -> Reg instance GHC.Show.Show BNFC.Regex.CharClassAtom instance GHC.Classes.Ord BNFC.Regex.CharClassAtom instance GHC.Classes.Eq BNFC.Regex.CharClassAtom instance GHC.Show.Show BNFC.Regex.CharClassUnion instance GHC.Classes.Ord BNFC.Regex.CharClassUnion instance GHC.Classes.Eq BNFC.Regex.CharClassUnion instance GHC.Show.Show BNFC.Regex.CharClass instance GHC.Classes.Ord BNFC.Regex.CharClass instance GHC.Classes.Eq BNFC.Regex.CharClass instance BNFC.Regex.ToReg BNFC.Regex.CharClassUnion instance BNFC.Regex.ToReg BNFC.Regex.RC instance BNFC.Regex.ToReg BNFC.Regex.CharClass instance GHC.Base.Semigroup BNFC.Regex.CharClassUnion instance GHC.Base.Monoid BNFC.Regex.CharClassUnion module BNFC.Utils -- | The name of a module, e.g. Foo.Abs, Foo.Print etc. type ModuleName = String -- | Generalization of when. when :: Monoid m => Bool -> m -> m -- | Generalization of unless. unless :: Monoid m => Bool -> m -> m -- | Invoke continuation for non-empty list. unlessNull :: Monoid m => [a] -> ([a] -> m) -> m -- | Invoke continuation for non-empty list. unlessNull' :: Monoid m => [a] -> (a -> [a] -> m) -> m -- | when for the monoid of endofunctions 'a -> a'. applyWhen :: Bool -> (a -> a) -> a -> a -- | unless for the monoid of endofunctions 'a -> a'. applyUnless :: Bool -> (a -> a) -> a -> a -- | Non-monadic forM. for :: [a] -> (a -> b) -> [b] -- | Generalization of forM to Monoid. whenJust :: Monoid m => Maybe a -> (a -> m) -> m -- | Rotation of maybe. caseMaybe :: Maybe a -> b -> (a -> b) -> b -- | Diagrammatic composition. (>.>) :: (a -> b) -> (b -> c) -> a -> c infixr 8 >.> -- | Converts an uncurried function to a curried function. curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d -- | Converts a curried function to a function on a triple. uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d -- | Give a telling name to the electric monkey. singleton :: a -> [a] -- | Get the first element of a list, fallback for empty list. headWithDefault :: a -> [a] -> a -- | Apply a function to the head of a list. mapHead :: (a -> a) -> [a] -> [a] -- | spanEnd p l == reverse (span p (reverse l)). -- -- Invariant: l == front ++ end where (end, front) = spanEnd p l -- -- (From package ghc, module Util.) spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) -- | Returns lists of elements whose normal form appears more than once. -- --
--   >>> duplicatesOn id  [5,1,2,5,1]
--   [1 :| [1],5 :| [5]]
--   
--   >>> duplicatesOn abs [5,-5,1]
--   [5 :| [-5]]
--   
duplicatesOn :: (Foldable t, Ord b) => (a -> b) -> t a -> [List1 a] -- | Group consecutive elements that have the same normalform. groupOn :: Eq b => (a -> b) -> [a] -> [List1 a] -- | Keep only the first of consecutive elements that have the same -- normalform. uniqOn :: Eq b => (a -> b) -> [a] -> [a] -- | Get a numeric suffix if it exists. -- --
--   >>> hasNumericSuffix "hello world"
--   Nothing
--   
--   >>> hasNumericSuffix "a1b2"
--   Just ("a1b",2)
--   
--   >>> hasNumericSuffix "1234"
--   Just ("",1234)
--   
hasNumericSuffix :: String -> Maybe (String, Integer) -- | Concatenate strings by a space. (+++) :: String -> String -> String infixr 5 +++ -- | Concatenate strings by a newline. (++++) :: String -> String -> String infixr 5 ++++ -- | Concatenate strings by an underscore. (+-+) :: String -> String -> String infixr 5 +-+ -- | Concatenate strings by a dot. (+.+) :: String -> String -> String infixr 5 +.+ -- | Wrap in parentheses if condition holds. parensIf :: Bool -> String -> String -- | Pad a string on the right by spaces to reach the desired length. pad :: Int -> String -> String -- | Make a list of rows with left-aligned columns from a matrix. table :: String -> [[String]] -> [String] -- | Generate a name in the given case style taking into account the -- reserved word of the language. Note that despite the fact that those -- name are mainly to be used in code rendering (type Doc), we return a -- String here to allow further manipulation of the name (like -- disambiguation) which is not possible in the Doc type. -- -- Examples: -- --
--   >>> mkName [] LowerCase "FooBAR"
--   "foobar"
--   
-- --
--   >>> mkName [] UpperCase "FooBAR"
--   "FOOBAR"
--   
-- --
--   >>> mkName [] SnakeCase "FooBAR"
--   "foo_bar"
--   
-- --
--   >>> mkName [] CamelCase "FooBAR"
--   "FooBAR"
--   
-- --
--   >>> mkName [] CamelCase "Foo_bar"
--   "FooBar"
--   
-- --
--   >>> mkName [] MixedCase "FooBAR"
--   "fooBAR"
--   
-- --
--   >>> mkName ["foobar"] LowerCase "FooBAR"
--   "foobar_"
--   
-- --
--   >>> mkName ["foobar", "foobar_"] LowerCase "FooBAR"
--   "foobar__"
--   
mkName :: [String] -> NameStyle -> String -> String -- | Same as above but accept a list as argument and make sure that the -- names generated are uniques. -- --
--   >>> mkNames ["c"] LowerCase ["A", "b_", "a_", "c"]
--   ["a1","b","a2","c_"]
--   
mkNames :: [String] -> NameStyle -> [String] -> [String] -- | Different case style data NameStyle -- | e.g. lowercase LowerCase :: NameStyle -- | e.g. UPPERCASE UpperCase :: NameStyle -- | e.g. snake_case SnakeCase :: NameStyle -- | e.g. CamelCase CamelCase :: NameStyle -- | e.g. mixedCase MixedCase :: NameStyle -- | Keep original capitalization and form. OrigCase :: NameStyle -- | Ident to lower case. >>> lowerCase MyIdent myident lowerCase :: String -> Doc -- | Ident to upper case. >>> upperCase MyIdent MYIDENT upperCase :: String -> Doc -- | To mixed case. >>> mixedCase "my_ident" myIdent mixedCase :: String -> Doc -- | Ident to camel case. >>> camelCase "my_ident" MyIdent camelCase :: String -> Doc camelCase_ :: String -> String -- | To snake case. >>> snakeCase MyIdent my_ident snakeCase :: String -> Doc snakeCase_ :: String -> String -- | Replace all occurences of a value by another value replace :: Eq a => a -> a -> [a] -> [a] -- | Write a file, after making a backup of an existing file with the same -- name. If an old version of the file exist and the new version is the -- same, keep the old file and don't create a .bak file. / New version by -- TH, 2010-09-23 writeFileRep :: FilePath -> String -> IO () -- | A function that renders a c-like string with escaped characters. Note -- that although it's called cstring, this can be used with most (all) -- backend as they seem to mostly share escaping conventions. The c in -- the name is barely an homage for C being the oldest language in the -- lot. -- --
--   >>> cstring "foobar"
--   "foobar"
--   
-- --
--   >>> cstring "foobar\""
--   "foobar\""
--   
cstring :: String -> Doc getZonedTimeTruncatedToSeconds :: IO ZonedTime -- | Print a symbol as typical token name, like "(" as LPAREN. symbolToName :: String -> Maybe String instance GHC.Classes.Eq BNFC.Utils.NameStyle instance GHC.Show.Show BNFC.Utils.NameStyle module BNFC.CF type List1 = NonEmpty -- | A context free grammar consists of a set of rules and some extended -- information (e.g. pragmas, literals, symbols, keywords). type CF = CFG RFun -- | A rule consists of a function name, a main category and a sequence of -- terminals and non-terminals. -- --
--   function_name . Main_Cat ::= sequence
--   
type Rule = Rul RFun -- | Polymorphic rule type. data Rul function Rule :: function -> RCat -> SentForm -> InternalRule -> Rul function -- | The function (semantic action) of a rule. In order to be able to -- generate data types this must be a constructor (or an identity -- function). [funRule] :: Rul function -> function -- | The value category, i.e., the defined non-terminal. [valRCat] :: Rul function -> RCat -- | The sentential form, i.e., the list of (non)terminals in the -- right-hand-side of a rule. [rhsRule] :: Rul function -> SentForm -- | Is this an "internal" rule only for the AST and printing, not for -- parsing? [internal] :: Rul function -> InternalRule data InternalRule -- | internal rule (only for AST & printer) Internal :: InternalRule -- | ordinary rule (also for parser) Parsable :: InternalRule -- | A sentential form is a sequence of non-terminals or terminals. type SentForm = [Either Cat String] -- | Type of context-free grammars (GFG). data CFG function CFG :: [Pragma] -> Set Cat -> [Literal] -> [Symbol] -> [KeyWord] -> [Cat] -> [Rul function] -> Signature -> CFG function [cfgPragmas] :: CFG function -> [Pragma] -- | Categories used by the parser. [cfgUsedCats] :: CFG function -> Set Cat -- | Char, String, Ident, Integer, Double. Strings are -- quoted strings, and Idents are unquoted. [cfgLiterals] :: CFG function -> [Literal] -- | Symbols in the grammar, e.g. “*”, “->”. [cfgSymbols] :: CFG function -> [Symbol] -- | Reserved words, e.g. if, while. [cfgKeywords] :: CFG function -> [KeyWord] -- | Categories that can be made left-recursive. [cfgReversibleCats] :: CFG function -> [Cat] [cfgRules] :: CFG function -> [Rul function] -- | Types of rule labels, computed from cfgRules. [cfgSignature] :: CFG function -> Signature -- | Types of the rule labels, together with the position of the rule -- label. type Signature = Map String (WithPosition Type) -- | Type of a non-terminal. type Base = Base' String data Base' a BaseT :: a -> Base' a ListT :: Base' a -> Base' a -- | Type of a rule label. data Type FunT :: [Base] -> Base -> Type -- | Placeholder for a type. dummyBase :: Base -- | Placeholder for a function type. dummyType :: Type -- | Expressions for function definitions. data Exp' f -- | (Possibly defined) label applied to expressions. The function -- Type is inferred by the type checker. App :: f -> Type -> [Exp' f] -> Exp' f -- | Function parameter. Var :: String -> Exp' f LitInt :: Integer -> Exp' f LitDouble :: Double -> Exp' f LitChar :: Char -> Exp' f LitString :: String -> Exp' f type Exp = Exp' String -- | Pragmas. data Pragma -- | for single line comments CommentS :: String -> Pragma -- | for multiple-line comments. CommentM :: (String, String) -> Pragma -- | for tokens TokenReg :: RString -> Bool -> Reg -> Pragma EntryPoints :: [RCat] -> Pragma Layout :: LayoutKeyWords -> Pragma LayoutStop :: [KeyWord] -> Pragma -- | Separator for top-level layout. LayoutTop :: Symbol -> Pragma FunDef :: Define -> Pragma data Define Define :: RFun -> Telescope -> Exp -> Base -> Define [defName] :: Define -> RFun -- | Argument types inferred by the type checker. [defArgs] :: Define -> Telescope [defBody] :: Define -> Exp -- | Type of the body, inferred by the type checker. [defType] :: Define -> Base -- | Function arguments with type. type Telescope = [(String, Base)] -- | For use with partitionEithers. isFunDef :: Pragma -> Either Pragma Define -- | All define pragmas of the grammar. definitions :: CFG f -> [Define] type LayoutKeyWords = [(KeyWord, Delimiters)] -- | List delimiters. data Delimiters Delimiters :: Symbol -> Symbol -> Symbol -> Delimiters -- | List separator. [listSep] :: Delimiters -> Symbol -- | List opening delimiter. [listOpen] :: Delimiters -> Symbol -- | List closing delimiter. [listClose] :: Delimiters -> Symbol -- | User-defined regular expression tokens tokenPragmas :: CFG f -> [(TokenCat, Reg)] -- | The names of all user-defined tokens. tokenNames :: CFG f -> [String] layoutPragmas :: CF -> (Maybe Symbol, LayoutKeyWords, [KeyWord]) hasLayout_ :: (Maybe Symbol, LayoutKeyWords, [KeyWord]) -> Bool hasLayout :: CF -> Bool -- | Literal: builtin-token types Char, String, Ident, Integer, Double. type Literal = String type Symbol = String type KeyWord = String -- | Source positions. data Position NoPosition :: Position Position :: FilePath -> Int -> Int -> Position -- | Name of the grammar file. [posFile] :: Position -> FilePath -- | Line in the grammar file. [posLine] :: Position -> Int -- | Column in the grammar file. [posColumn] :: Position -> Int prettyPosition :: Position -> String data WithPosition a WithPosition :: Position -> a -> WithPosition a [wpPosition] :: WithPosition a -> Position [wpThing] :: WithPosition a -> a noPosition :: a -> WithPosition a -- | A "ranged string" (terminology from Agda code base). type RString = WithPosition String -- | Prefix string with pretty-printed position information. blendInPosition :: RString -> String type RCat = WithPosition Cat valCat :: Rul fun -> Cat npRule :: Fun -> Cat -> SentForm -> InternalRule -> Rule npIdentifier :: String -> Identifier -- | Categories are the non-terminals of the grammar. data Cat -- | Ordinary non-terminal. Cat :: String -> Cat -- | Token types (like Ident, Integer, ..., -- user-defined). TokenCat :: TokenCat -> Cat -- | List non-terminals, e.g., [Ident], [Exp], -- [Exp1]. ListCat :: Cat -> Cat -- | E.g. Exp1, Exp2. CoercCat :: String -> Integer -> Cat type TokenCat = String type BaseCat = String type NonTerminal = Cat -- | Render category symbols as strings catToStr :: Cat -> String -- | Reads a string into a category. This should only need to handle the -- case of simple categories (with or without coercion) since list -- categories are parsed in the grammar already. To be on the safe side -- here, we still call the parser function that parses categries. strToCat :: String -> Cat catString :: TokenCat catInteger :: TokenCat catDouble :: TokenCat catChar :: TokenCat catIdent :: TokenCat -- | Token categories corresponding to base types. baseTokenCatNames :: [TokenCat] specialCatsP :: [TokenCat] -- | Does the category correspond to a data type? isDataCat :: Cat -> Bool isDataOrListCat :: Cat -> Bool -- | Categories C1, C2,... (one digit at the end) are variants of C. This -- function returns true if two category are variants of the same -- abstract category. E.g. -- --
--   >>> sameCat (Cat "Abc") (CoercCat "Abc" 44)
--   True
--   
sameCat :: Cat -> Cat -> Bool -- | Removes precedence information. C1 => C, [C2] => [C] normCat :: Cat -> Cat normCatOfList :: Cat -> Cat -- | When given a list Cat, i.e. '[C]', it removes the square brackets, and -- adds the prefix List, i.e. ListC. (for Happy and Latex) identCat :: Cat -> String identType :: Base -> String -- | Reconstruct (non-coercion) category from a type, given a list of what -- should be the token categories. catOfType :: [TokenCat] -> Base -> Cat isList :: Cat -> Bool -- | Get the underlying category identifier. baseCat :: Cat -> Either BaseCat TokenCat isTokenCat :: Cat -> Bool maybeTokenCat :: Cat -> Maybe TokenCat -- | Unwraps the list constructor from the category name. E.g. [C1] -- => C1. catOfList :: Cat -> Cat -- | Fun is the function name of a rule. type Fun = String type RFun = RString class IsFun a funName :: IsFun a => a -> String isNilFun :: IsFun a => a -> Bool isOneFun :: IsFun a => a -> Bool isConsFun :: IsFun a => a -> Bool isConcatFun :: IsFun a => a -> Bool -- | Is this function just a coercion? (I.e. the identity) isCoercion :: IsFun a => a -> Bool funNameSatisfies :: IsFun a => (String -> Bool) -> a -> Bool isDefinedRule :: IsFun a => a -> Bool isProperLabel :: IsFun a => a -> Bool isNilCons :: IsFun a => a -> Bool -- | The abstract syntax of a grammar. type Data = (Cat, [(String, [Cat])]) -- | firstEntry returns the first of the entrypoints, or -- (if none), the first parsable Category appearing in the -- grammar. firstEntry :: CF -> Cat -- | Constructors and categories. allNames :: CF -> [RString] -- | Get all elements with more than one occurrence. filterNonUnique :: Ord a => [a] -> [a] -- | Extract the comment pragmas. commentPragmas :: [Pragma] -> [Pragma] lookupRule :: Eq f => f -> [Rul f] -> Maybe (Cat, SentForm) -- | Returns all parseable rules that construct the given Cat. Whitespace -- separators have been removed. rulesForCat :: CF -> Cat -> [Rule] removeWhiteSpaceSeparators :: Rul f -> Rul f -- | Modify the rhsRule part of a Rule. mapRhs :: (SentForm -> SentForm) -> Rul f -> Rul f -- | Like rulesForCat but for normalized value categories. I.e., -- `rulesForCat (Cat Exp)` will return rules for category Exp but -- also Exp1, Exp2... in case of coercion rulesForNormalizedCat :: CF -> Cat -> [Rule] -- | As rulesForCat, but this version doesn't exclude internal rules. rulesForCat' :: CF -> Cat -> [Rule] -- | Get all categories of a grammar matching the filter. (No Cat w/o -- production returned; no duplicates.) allCats :: (InternalRule -> Bool) -> CFG f -> [Cat] -- | Get all categories of a grammar. (No Cat w/o production returned; no -- duplicates.) reallyAllCats :: CFG f -> [Cat] allParserCats :: CFG f -> [Cat] -- | Gets all normalized identified Categories allCatsIdNorm :: CF -> [RString] -- | Get all normalized Cat allCatsNorm :: CF -> [Cat] -- | Get all normalized Cat allParserCatsNorm :: CFG f -> [Cat] -- | Is the category is used on an rhs? Includes internal rules. isUsedCat :: CFG f -> Cat -> Bool -- | Group all parsable categories with their rules. Deletes whitespace -- separators, as they will not become part of the parsing rules. ruleGroups :: CF -> [(Cat, [Rule])] -- | Group all categories with their rules including internal rules. ruleGroupsInternals :: CF -> [(Cat, [Rule])] -- | Get all literals of a grammar. (e.g. String, Double) literals :: CFG f -> [TokenCat] -- | Get the keywords of a grammar. reservedWords :: CFG f -> [String] -- | Canonical, numbered list of symbols and reserved words. (These do not -- end up in the AST.) cfTokens :: CFG f -> [(String, Int)] -- | Comments can be defined by the comment pragma comments :: CF -> ([(String, String)], [String]) -- | Number of block comment forms defined in the grammar file. numberOfBlockCommentForms :: CF -> Int -- | Whether the grammar uses the predefined Ident type. hasIdent :: CFG f -> Bool -- | Categories corresponding to tokens. These end up in the AST. (unlike -- tokens returned by cfTokens) specialCats :: CF -> [TokenCat] -- | Return the abstract syntax of the grammar. All categories are -- normalized, so a rule like: EAdd . Exp2 ::= Exp2 "+" Exp3 ; Will give -- the following signature: EAdd : Exp -> Exp -> Exp getAbstractSyntax :: CF -> [Data] -- | All the functions below implement the idea of getting the abstract -- syntax of the grammar with some variation but they seem to do a poor -- job at handling corner cases involving coercions. Use -- getAbstractSyntax instead if possible. cf2data' :: (Cat -> Bool) -> CF -> [Data] cf2data :: CF -> [Data] cf2dataLists :: CF -> [Data] specialData :: CF -> [Data] -- | Get the type of a rule label. sigLookup :: IsFun a => a -> CF -> Maybe (WithPosition Type) -- | Checks if the rule is parsable. isParsable :: Rul f -> Bool hasNilRule :: [Rule] -> Maybe Rule -- | Gets the singleton rule out of the rules for a list. hasSingletonRule :: [Rule] -> Maybe Rule -- | Sort rules by descending precedence. sortRulesByPrecedence :: [Rule] -> [(Integer, Rule)] -- | Is the given category a list category parsing also empty lists? isEmptyListCat :: CF -> Cat -> Bool isNonterm :: Either Cat String -> Bool revSepListRule :: Rul f -> Rul f findAllReversibleCats :: CF -> [Cat] isEmptyNilRule :: IsFun a => Rul a -> Bool -- | Returns the precedence of a category symbol. E.g. >>> precCat -- (CoercCat Abc 4) 4 precCat :: Cat -> Integer precRule :: Rul f -> Integer -- | Defines or uses the grammar token types like Ident? Excludes -- position tokens. hasIdentLikeTokens :: CFG g -> Bool -- | Defines or uses the grammar token types or Ident? hasTextualTokens :: CFG g -> Bool -- | Is there a position token declaration in the grammar? hasPositionTokens :: CFG g -> Bool -- | Does the category have a position stored in AST? isPositionCat :: CFG f -> TokenCat -> Bool -- | Categories that are entry points to the parser. -- -- These are either the declared entrypoints (in the original -- order), or, if no entrypoints were declared explicitly, all -- parsable categories (in the order of declaration in the grammar file). allEntryPoints :: CFG f -> List1 Cat instance GHC.Classes.Eq BNFC.CF.InternalRule instance GHC.Base.Functor BNFC.CF.Base' instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.CF.Base' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.CF.Base' a) instance GHC.Classes.Ord BNFC.CF.Type instance GHC.Classes.Eq BNFC.CF.Type instance GHC.Classes.Eq f => GHC.Classes.Eq (BNFC.CF.Exp' f) instance GHC.Show.Show BNFC.CF.Delimiters instance GHC.Classes.Ord BNFC.CF.Position instance GHC.Classes.Eq BNFC.CF.Position instance GHC.Show.Show BNFC.CF.Position instance Data.Traversable.Traversable BNFC.CF.WithPosition instance Data.Foldable.Foldable BNFC.CF.WithPosition instance GHC.Base.Functor BNFC.CF.WithPosition instance GHC.Show.Show a => GHC.Show.Show (BNFC.CF.WithPosition a) instance GHC.Classes.Ord BNFC.CF.Cat instance GHC.Classes.Eq BNFC.CF.Cat instance GHC.Base.Functor BNFC.CF.Rul instance GHC.Classes.Eq function => GHC.Classes.Eq (BNFC.CF.Rul function) instance GHC.Base.Functor BNFC.CF.CFG instance (BNFC.CF.IsFun f, BNFC.PrettyPrint.Pretty f) => BNFC.PrettyPrint.Pretty (BNFC.CF.Exp' f) instance BNFC.CF.IsFun GHC.Base.String instance BNFC.CF.IsFun a => BNFC.CF.IsFun (BNFC.CF.WithPosition a) instance BNFC.CF.IsFun a => BNFC.CF.IsFun (BNFC.CF.Rul a) instance BNFC.CF.IsFun a => BNFC.CF.IsFun (k, a) instance Data.String.IsString BNFC.CF.RFun instance BNFC.PrettyPrint.Pretty function => BNFC.PrettyPrint.Pretty (BNFC.CF.Rul function) instance GHC.Show.Show BNFC.CF.Cat instance BNFC.PrettyPrint.Pretty BNFC.CF.Cat instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.CF.WithPosition a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.CF.WithPosition a) instance BNFC.PrettyPrint.Pretty a => BNFC.PrettyPrint.Pretty (BNFC.CF.WithPosition a) instance GHC.Show.Show BNFC.CF.Type instance GHC.Show.Show BNFC.CF.Base -- | Type checker for defined syntax constructors define f xs = e. module BNFC.TypeChecker runTypeChecker :: Err a -> Either String a -- | Entry point. checkDefinitions :: CF -> Err CF checkDefinition' :: ListConstructors -> Context -> RFun -> [String] -> Exp -> Err (Telescope, (Exp, Base)) -- | Create context containing the types of all labels, computed from the -- rules. -- -- Fail if a label is used at different types. buildSignature :: [Rule] -> Err Signature buildContext :: CF -> Context -- | User-defined token types. ctxTokens :: Context -> [String] isToken :: String -> Context -> Bool data ListConstructors LC :: (Base -> (String, Type)) -> (Base -> (String, Type)) -> ListConstructors -- | Base is the element type. Type the list type. [nil] :: ListConstructors -> Base -> (String, Type) [cons] :: ListConstructors -> Base -> (String, Type) instance Control.Monad.Reader.Class.MonadReader BNFC.CF.Position BNFC.TypeChecker.Err instance GHC.Base.Monad BNFC.TypeChecker.Err instance GHC.Base.Applicative BNFC.TypeChecker.Err instance GHC.Base.Functor BNFC.TypeChecker.Err instance Control.Monad.Error.Class.MonadError GHC.Base.String BNFC.TypeChecker.Err module BNFC.Lexing mkLexer :: CF -> [(Reg, LexType)] data LexType LexComment :: LexType LexToken :: String -> LexType LexSymbols :: LexType -- | Create regex for multiline comments. -- --
--   >>> debugPrint $ mkRegMultilineComment "<" ">"
--   '<'(char-'>')*'>'
--   
-- --
--   >>> debugPrint $ mkRegMultilineComment "/*" "*/"
--   {"/*"}(char-'*')*'*'((char-["*/"])(char-'*')*'*'|'*')*'/'
--   
-- --
--   >>> debugPrint $ mkRegMultilineComment "<!--" "-->"
--   {"<!--"}(char-'-')*'-'((char-'-')+'-')*'-'((char-["->"])(char-'-')*'-'((char-'-')+'-')*'-'|'-')*'>'
--   
mkRegMultilineComment :: String -> String -> Reg debugPrint :: Reg -> IO () -- | Check whether generated AST will have empty types. -- -- Internal rules are included. -- -- We compute by a saturation algorithm which token types are used in -- which non-terminal. A non-terminal does not use any token types, we -- flag an empty type. module BNFC.Check.EmptyTypes -- | Compute the categories that have empty data type declarations in the -- abstract syntax. Disregards list types. emptyData :: forall f. IsFun f => [Rul f] -> [RCat] module BNFC.Backend.Common.OOAbstract data CAbs CAbs :: [String] -> [(String, Bool)] -> [String] -> [Fun] -> [(String, [CAbsRule])] -> [String] -> [Fun] -> CAbs [tokentypes] :: CAbs -> [String] [listtypes] :: CAbs -> [(String, Bool)] [absclasses] :: CAbs -> [String] [conclasses] :: CAbs -> [Fun] [signatures] :: CAbs -> [(String, [CAbsRule])] [postokens] :: CAbs -> [String] [defineds] :: CAbs -> [Fun] type CAbsRule = (Fun, [(String, Bool, String)]) allClasses :: CAbs -> [String] allNonClasses :: CAbs -> [String] cf2cabs :: CF -> CAbs basetypes :: [(String, String)] classVar :: String -> String pointerIf :: Bool -> String -> String module BNFC.Backend.Common.NamedVariables type IVar = (String, Int) type UserDef = TokenCat -- | A symbol-mapping environment. type SymEnv = KeywordEnv -- | Map keywords to their token name. type KeywordEnv = [(String, String)] -- | Map keywords and user-defined token types to their token name. type SymMap = Map SymKey String data SymKey -- | Keyword like "(", "while", "true", ... Keyword :: String -> SymKey -- | Token type like Integer, Char, ... Tokentype :: String -> SymKey -- | Converts a list of categories into their types to be used as instance -- variables. If a category appears only once, it is given the number 0, -- if it appears more than once, its occurrences are numbered from 1. ex: -- --
--   >>> getVars [Cat "A", Cat "B", Cat "A"]
--   [("A",1),("B",0),("A",2)]
--   
getVars :: [Cat] -> [IVar] -- | Anotate the right hand side of a rule with variable names for the -- non-terminals. >>> numVars [Left (Cat A), Right "+", -- Left (Cat B)] [Left (A,a_),Right "+",Left (B,b_)] >>> -- numVars [Left (Cat A), Left (Cat A), Right ";"] [Left -- (A,a_1),Left (A,a_2),Right ";"] numVars :: [Either Cat a] -> [Either (Cat, Doc) a] fixCoercions :: [(Cat, [Rule])] -> [(Cat, [Rule])] varName :: String -> String showNum :: Int -> String firstLowerCase :: String -> String instance GHC.Show.Show BNFC.Backend.Common.NamedVariables.SymKey instance GHC.Classes.Ord BNFC.Backend.Common.NamedVariables.SymKey instance GHC.Classes.Eq BNFC.Backend.Common.NamedVariables.SymKey module BNFC.Backend.Txt2Tag cfToTxt :: String -> CF -> String t2tComment :: String -> String module BNFC.Backend.Java.Utils -- | Make a Java line comment comment :: String -> String javaReserved :: [String] -- | Append an underscore if there is a clash with a java or ANTLR keyword. -- E.g. Grammar clashes with ANTLR keyword "grammar" since we -- sometimes need the upper and sometimes the lower case version of -- Grammar in the generated parser. getRuleName :: String -> String getLabelName :: Fun -> String getLastInPackage :: String -> String -- | Make a new entrypoint NT for an existing NT. startSymbol :: String -> String module BNFC.Backend.Java.CFtoAntlr4Lexer -- | Creates a lexer grammar. Since antlr token identifiers must start with -- an uppercase symbol, I prepend Surrogate_id_SYMB_ to the -- identifier. This introduces risks of clashes if somebody uses the same -- identifier for user defined tokens. This is not handled. returns the -- environment because the parser uses it. cf2AntlrLex :: String -> CF -> (Doc, KeywordEnv) module BNFC.Backend.Java.CFtoAllVisitor cf2AllVisitor :: String -> String -> CF -> String module BNFC.Backend.Java.CFtoAbstractVisitor cf2AbstractVisitor :: String -> String -> CF -> String module BNFC.Backend.Haskell.CFtoLayout data TokSymbol TokSymbol :: String -> Int -> TokSymbol data LayoutDelimiters LayoutDelimiters :: TokSymbol -> Maybe TokSymbol -> Maybe TokSymbol -> LayoutDelimiters cf2Layout :: String -> String -> CF -> String instance GHC.Show.Show BNFC.Backend.Haskell.CFtoLayout.TokSymbol instance GHC.Show.Show BNFC.Backend.Haskell.CFtoLayout.LayoutDelimiters -- | Functions common to different backends. module BNFC.Backend.Common unicodeAndSymbols :: CF -> [String] asciiKeywords :: CF -> [String] -- | Representation of the empty word as Flex regular expression flexEps :: String switchByPrecedence :: Doc -> [(Integer, Doc)] -> [Doc] module BNFC.Backend.C.RegToFlex printRegFlex :: Reg -> String instance BNFC.Backend.C.RegToFlex.Print BNFC.Abs.Identifier instance BNFC.Backend.C.RegToFlex.Print BNFC.Abs.Reg module BNFC.Backend.CPP.PrettyPrinter cf2CPPPrinter :: Bool -> Maybe String -> CF -> (String, String) prRender :: Bool -> String module BNFC.Backend.CPP.Naming cReservedWords :: [String] cppReservedWords :: [String] mkVariable :: String -> String sanitizeC :: String -> String sanitizeCpp :: String -> String module BNFC.Backend.CPP.STL.CFtoCVisitSkelSTL cf2CVisitSkel :: Bool -> Maybe String -> CF -> (String, String) module BNFC.Backend.C.CFtoCSkel cf2CSkel :: CF -> (String, String) module BNFC.Backend.C.CFtoCPrinter -- | Produces (.h file, .c file). cf2CPrinter :: CF -> (String, String) module BNFC.Options -- | To decouple the option parsing from the execution of the program, we -- introduce a data structure that holds the result of the parsing of the -- arguments. data Mode UsageError :: String -> Mode Help :: Mode License :: Mode Version :: Mode Target :: SharedOptions -> FilePath -> Mode -- | Target languages data Target TargetC :: Target TargetCpp :: Target TargetCppNoStl :: Target TargetHaskell :: Target TargetHaskellGadt :: Target TargetLatex :: Target TargetJava :: Target TargetOCaml :: Target TargetPygments :: Target TargetCheck :: Target type Backend = SharedOptions " Options" -> CF " Grammar" -> IO () -- | Main parsing function parseMode :: [String] -> (Mode, UsageWarnings) usage :: String help :: String versionString :: String -- | This is the option record that is passed to the different backends. data SharedOptions Options :: FilePath -> String -> FilePath -> Bool -> Target -> Maybe String -> InPackage -> RecordPositions -> Ansi -> Bool -> Bool -> Bool -> AlexVersion -> TokenText -> HappyMode -> Int -> Bool -> OCamlParser -> JavaLexerParser -> Bool -> Bool -> SharedOptions -- | The input file BNFC processes. [lbnfFile] :: SharedOptions -> FilePath -- | The language we generate: the basename of lbnfFile. [lang] :: SharedOptions -> String -- | Target directory for generated files. [outDir] :: SharedOptions -> FilePath -- | Ignore errors as much as possible? [force] :: SharedOptions -> Bool -- | E.g. --haskell. [target] :: SharedOptions -> Target -- | The name of the Makefile to generate or Nothing for no Makefile. [make] :: SharedOptions -> Maybe String -- | The hierarchical package to put the modules in, or Nothing. [inPackage] :: SharedOptions -> InPackage -- | Add and set line_number field for syntax classes [linenumbers] :: SharedOptions -> RecordPositions -- | Restrict to the ANSI language standard (C/C++)? [ansi] :: SharedOptions -> Ansi -- | Option -d. [inDir] :: SharedOptions -> Bool -- | Option --functor. Make AST functorial? [functor] :: SharedOptions -> Bool -- | Option --generic. Derive Data, Generic, Typeable? [generic] :: SharedOptions -> Bool -- | Options --alex. [alexMode] :: SharedOptions -> AlexVersion -- | Options --bytestrings, --string-token, and -- --text-token. [tokenText] :: SharedOptions -> TokenText -- | Happy option --glr. [glr] :: SharedOptions -> HappyMode -- | Options --xml, generate DTD and XML printers. [xml] :: SharedOptions -> Int -- | Option --agda. Create bindings for Agda? [agda] :: SharedOptions -> Bool -- | Option --menhir to switch to Menhir. [ocamlParser] :: SharedOptions -> OCamlParser [javaLexerParser] :: SharedOptions -> JavaLexerParser -- | Generate Visual Studio solution/project files. [visualStudio] :: SharedOptions -> Bool -- | Windows Communication Foundation. [wcf] :: SharedOptions -> Bool defaultOptions :: SharedOptions -- | Check whether an option is unchanged from the default. isDefault :: Eq a => (SharedOptions -> a) -> SharedOptions -> Bool -- | Print options as input to BNFC. -- -- unwords [ "bnfc", printOptions opts ] should call bnfc with -- the same options as the current instance. printOptions :: SharedOptions -> String -- | Which version of Alex is targeted? data AlexVersion Alex3 :: AlexVersion -- | Happy modes data HappyMode Standard :: HappyMode GLR :: HappyMode -- | Which parser generator for ocaml? data OCamlParser OCamlYacc :: OCamlParser Menhir :: OCamlParser -- | Which Java backend? data JavaLexerParser JLexCup :: JavaLexerParser JFlexCup :: JavaLexerParser Antlr4 :: JavaLexerParser -- | Line numbers or not? data RecordPositions RecordPositions :: RecordPositions NoRecordPositions :: RecordPositions -- | How to represent token content in the Haskell backend? data TokenText -- | Represent strings as String. StringToken :: TokenText -- | Represent strings as ByteString. ByteStringToken :: TokenText -- | Represent strings as Data.Text. TextToken :: TokenText -- | Restrict to ANSI standard (C/C++)? data Ansi Ansi :: Ansi BeyondAnsi :: Ansi -- | Package name (C++ and Java backends). type InPackage = Maybe String removedIn290 :: String -- | A translation function to maintain backward compatibility with the old -- option syntax. translateOldOptions :: [String] -> ParseOpt [String] instance GHC.Classes.Ord BNFC.Options.Target instance GHC.Enum.Enum BNFC.Options.Target instance GHC.Enum.Bounded BNFC.Options.Target instance GHC.Classes.Eq BNFC.Options.Target instance GHC.Enum.Enum BNFC.Options.AlexVersion instance GHC.Enum.Bounded BNFC.Options.AlexVersion instance GHC.Classes.Ord BNFC.Options.AlexVersion instance GHC.Classes.Eq BNFC.Options.AlexVersion instance GHC.Show.Show BNFC.Options.AlexVersion instance GHC.Classes.Ord BNFC.Options.HappyMode instance GHC.Enum.Enum BNFC.Options.HappyMode instance GHC.Enum.Bounded BNFC.Options.HappyMode instance GHC.Show.Show BNFC.Options.HappyMode instance GHC.Classes.Eq BNFC.Options.HappyMode instance GHC.Classes.Ord BNFC.Options.OCamlParser instance GHC.Show.Show BNFC.Options.OCamlParser instance GHC.Classes.Eq BNFC.Options.OCamlParser instance GHC.Classes.Ord BNFC.Options.JavaLexerParser instance GHC.Show.Show BNFC.Options.JavaLexerParser instance GHC.Classes.Eq BNFC.Options.JavaLexerParser instance GHC.Classes.Ord BNFC.Options.RecordPositions instance GHC.Show.Show BNFC.Options.RecordPositions instance GHC.Classes.Eq BNFC.Options.RecordPositions instance GHC.Show.Show BNFC.Options.Ansi instance GHC.Classes.Ord BNFC.Options.Ansi instance GHC.Classes.Eq BNFC.Options.Ansi instance GHC.Show.Show BNFC.Options.TokenText instance GHC.Classes.Ord BNFC.Options.TokenText instance GHC.Classes.Eq BNFC.Options.TokenText instance GHC.Show.Show BNFC.Options.SharedOptions instance GHC.Classes.Ord BNFC.Options.SharedOptions instance GHC.Classes.Eq BNFC.Options.SharedOptions instance GHC.Classes.Ord BNFC.Options.Mode instance GHC.Show.Show BNFC.Options.Mode instance GHC.Classes.Eq BNFC.Options.Mode instance BNFC.Options.Maintained BNFC.Options.Target instance BNFC.Options.Maintained BNFC.Options.AlexVersion instance BNFC.Options.Maintained BNFC.Options.HappyMode instance GHC.Base.Semigroup (BNFC.Options.ParseOpt ()) instance GHC.Base.Monoid (BNFC.Options.ParseOpt ()) instance GHC.Show.Show BNFC.Options.Target -- | Check LBNF input file and turn it into the CF internal -- representation. module BNFC.GetCF -- | Entrypoint. parseCF :: SharedOptions -> Target -> String -> IO CF checkRule :: CF -> Rule -> Maybe String -- | Translate a rule item (terminal or non terminal) It also sanitizes the -- terminals a bit by skipping empty terminals or splitting multiwords -- terminals. This means that the following rule -- --
--   Foo. S ::= "foo bar" ""
--   
-- -- is equivalent to -- --
--   Foo. S ::= "foo" "bar"
--   
transItem :: Item -> [Either Cat String] instance Control.Monad.Error.Class.MonadError GHC.Base.String BNFC.GetCF.Trans instance Control.Monad.Reader.Class.MonadReader BNFC.Options.SharedOptions BNFC.GetCF.Trans instance GHC.Base.Monad BNFC.GetCF.Trans instance GHC.Base.Applicative BNFC.GetCF.Trans instance GHC.Base.Functor BNFC.GetCF.Trans instance BNFC.GetCF.FixTokenCats a => BNFC.GetCF.FixTokenCats [a] instance BNFC.GetCF.FixTokenCats a => BNFC.GetCF.FixTokenCats (BNFC.CF.WithPosition a) instance (BNFC.GetCF.FixTokenCats a, GHC.Classes.Ord a) => BNFC.GetCF.FixTokenCats (Data.Set.Internal.Set a) instance BNFC.GetCF.FixTokenCats BNFC.CF.Cat instance BNFC.GetCF.FixTokenCats (Data.Either.Either BNFC.CF.Cat GHC.Base.String) instance BNFC.GetCF.FixTokenCats (BNFC.CF.Rul f) instance BNFC.GetCF.FixTokenCats BNFC.CF.Pragma instance BNFC.GetCF.FixTokenCats (BNFC.CF.CFG f) module BNFC.Backend.OCaml.OCamlUtil -- | Name of the parser generator. class OCamlParserName a ocamlParserName :: OCamlParserName a => a -> String fixType :: Cat -> String fixTypeQual :: String -> Cat -> String fixTypeUpper :: Cat -> String reservedOCaml :: [String] -- | Avoid clashes with keywords. sanitizeOcaml :: String -> String -- | Keywords of ocamllex. reservedOCamlLex :: [String] -- | Heuristics to produce name for ocamllex token definition that does not -- clash with the ocamllex keywords. ocamlTokenName :: String -> String mkTuple :: [String] -> String insertBar :: [String] -> [String] mutualDefs :: [String] -> [String] -- | Escape " and @@. TODO: escape unprintable characters!? mkEsc :: String -> String instance BNFC.Backend.OCaml.OCamlUtil.OCamlParserName BNFC.Options.OCamlParser instance BNFC.Backend.OCaml.OCamlUtil.OCamlParserName BNFC.Options.SharedOptions module BNFC.Backend.OCaml.CFtoOCamlTemplate cf2Template :: ModuleName -> ModuleName -> CF -> String module BNFC.Backend.OCaml.CFtoOCamlShow cf2show :: String -> ModuleName -> CF -> String showsFunQual :: (String -> String) -> Cat -> String module BNFC.Backend.OCaml.CFtoOCamlAbs cf2Abstract :: String -> CF -> String module BNFC.Backend.OCaml.CFtoOCamlYacc cf2ocamlyacc :: OCamlParser -> String -> CF -> String -- | map a CF terminal into a ocamlyacc token terminal :: CF -> String -> String epName :: Cat -> String module BNFC.Backend.OCaml.CFtoOCamlLex cf2ocamllex :: String -> String -> CF -> String instance BNFC.Backend.OCaml.CFtoOCamlLex.Print a => BNFC.Backend.OCaml.CFtoOCamlLex.Print [a] instance BNFC.Backend.OCaml.CFtoOCamlLex.Print GHC.Types.Char instance BNFC.Backend.OCaml.CFtoOCamlLex.Print BNFC.Abs.Identifier instance BNFC.Backend.OCaml.CFtoOCamlLex.Print BNFC.Abs.Reg module BNFC.Backend.Java.RegToJLex -- | Print a regular expression for the Java lexers. printRegJLex :: JavaLexerParser -> Reg -> String escapeChar :: JavaLexerParser -> Char -> String instance BNFC.Backend.Java.RegToJLex.Print a => BNFC.Backend.Java.RegToJLex.Print [a] instance BNFC.Backend.Java.RegToJLex.Print GHC.Types.Char instance BNFC.Backend.Java.RegToJLex.Print BNFC.Abs.Identifier instance BNFC.Backend.Java.RegToJLex.Print BNFC.Abs.Reg module BNFC.Backend.Java.CFtoJavaAbs15 -- | The result is a list of files (without file extension) which must be -- written to disk. The tuple is (FileName, FileContents) cf2JavaAbs :: FilePath -> String -> String -> CF -> RecordPositions -> [(FilePath, String)] -- | This makes up for the fact that there's no typedef in Java. typename :: String -> [UserDef] -> String -> String -- | Print the Java type corresponding to a category. cat2JavaType :: [UserDef] -> Cat -> String module BNFC.Backend.Java.CFtoVisitSkel15 cf2VisitSkel :: String -> String -> CF -> String module BNFC.Backend.Java.CFtoJavaPrinter15 cf2JavaPrinter :: String -> String -> CF -> String module BNFC.Backend.Java.CFtoFoldVisitor cf2FoldVisitor :: String -> String -> CF -> String module BNFC.Backend.Java.CFtoComposVisitor cf2ComposVisitor :: String -> String -> CF -> String module BNFC.Backend.Java.CFtoCup15 cf2Cup :: String -> String -> CF -> RecordPositions -> KeywordEnv -> String module BNFC.Backend.Java.CFtoAntlr4Parser -- | Creates the ANTLR parser grammar for this CF. The environment comes -- from CFtoAntlr4Lexer cf2AntlrParse :: String -> String -> CF -> RecordPositions -> KeywordEnv -> String module BNFC.Backend.Haskell.Utils -- | Haskell line comments. comment :: String -> String -- | Haskell line comment including mode hint for emacs. commentWithEmacsModeHint :: String -> String posType :: IsString a => a posConstr :: IsString a => a noPosConstr :: IsString a => a hasPositionClass :: IsString a => a hasPositionMethod :: IsString a => a noWarnUnusedMatches :: IsString a => a -- | Create a valid parser function name for a given category. -- --
--   >>> parserName (Cat "Abcd")
--   pAbcd
--   
-- --
--   >>> parserName (ListCat (Cat "Xyz"))
--   pListXyz
--   
parserName :: Cat -> Doc -- | Haskell's reserved words. hsReservedWords :: [String] -- | Avoid Haskell keywords plus additional reserved words. avoidReservedWords :: [String] -> String -> String -- | Modifier to avoid clashes in definition. mkDefName :: IsFun f => f -> String -- | Convert a function type to Haskell syntax in curried form. typeToHaskell :: Type -> String typeToHaskell' :: String -> Type -> String -- | Render a category from the grammar to a Haskell type. -- --
--   >>> catToType id empty (Cat "A")
--   A
--   
--   >>> catToType id empty (ListCat (Cat "A"))
--   [A]
--   
--   >>> catToType ("Foo." P.<>) empty (TokenCat "Ident")
--   Foo.Ident
--   
-- -- Note that there is no haskell type for coerced categories: they should -- be normalized: >>> catToType id empty (CoercCat Expr -- 2) Expr -- -- If a type parameter is given it is added to the type name: -- >>> catToType id (text "a") (Cat A) (A a) -- --
--   >>> catToType id (text "a") (ListCat (Cat "A"))
--   [A a]
--   
-- -- but not added to Token categories: >>> catToType ("Foo." -- P.<>) (text "a") (TokenCat Integer) Integer -- --
--   >>> catToType id (text "a") (ListCat (TokenCat "Integer"))
--   [Integer]
--   
-- --
--   >>> catToType id empty (ListCat (CoercCat "Exp" 2))
--   [Exp]
--   
-- --
--   >>> catToType ("Foo." P.<>) (text "()") (ListCat (CoercCat "Exp" 2))
--   [Foo.Exp ()]
--   
catToType :: (Doc -> Doc) -> Doc -> Cat -> Doc -- | Make a variable name for a category. catToVar :: [String] -> Cat -> String -- | Gives a list of variables usable for pattern matching. -- -- Example: Given the rule Aba. S ::= A B A ; with the generated -- data type data S = Aba A B A from the list of categories on -- the RHS of the rule [A,B,A], we generate the list [a1,b,a2] to be used -- in a pattern matching like case s of Aba a1 b a2 -> ... ... -- -- --
--   >>> catvars [] [Cat "A", Cat "B", Cat "A"]
--   [a1,b,a2]
--   
-- -- It should avoid reserved words: >>> catvars ["foo"] [Cat -- Foo, Cat IF, Cat Case, Cat Type, Cat -- If] [foo_,if_1,case_,type_,if_2] -- -- It uses a suffix -s to mark lists: >>> catvars [] [Cat -- A, ListCat (Cat A), ListCat (ListCat (Cat A))] -- [a,as_,ass] catvars :: [String] -> [Cat] -> [Doc] tokenTextImport :: TokenText -> [String] tokenTextType :: TokenText -> String tokenTextPack :: TokenText -> String -> String tokenTextPackParens :: TokenText -> String -> String tokenTextUnpack :: TokenText -> String -> String module BNFC.Backend.HaskellGADT.HaskellGADTCommon data Constructor Constructor :: Cat -> Fun -> Integer -> [(Cat, String)] -> [Either Cat String] -> Constructor [consCat] :: Constructor -> Cat [consFun] :: Constructor -> Fun [consPrec] :: Constructor -> Integer [consVars] :: Constructor -> [(Cat, String)] [consRhs] :: Constructor -> [Either Cat String] -- | Get category, function, and rhs categories paired with variable names. cf2cons :: CF -> [Constructor] isTreeType :: CF -> Cat -> Bool module BNFC.Backend.HaskellGADT.CFtoTemplateGADT cf2Template :: ModuleName -> ModuleName -> CF -> String module BNFC.Backend.Haskell.CFtoTemplate cf2Template :: ModuleName -> ModuleName -> Bool -> CF -> String module BNFC.Backend.Haskell.HsOpts type Options = SharedOptions absFile :: Options -> String absFileM :: Options -> String alexFile :: Options -> String alexFileHs :: Options -> String alexFileM :: Options -> String composOpFile :: Options -> String composOpFileM :: Options -> String happyFile :: Options -> String happyFileHs :: Options -> String happyFileM :: Options -> String txtFile :: Options -> String errFile :: Options -> String errFileM :: Options -> String templateFile :: Options -> String templateFileM :: Options -> String printerFile :: Options -> String printerFileM :: Options -> String layoutFile :: Options -> String layoutFileM :: Options -> String xmlFile :: Options -> String xmlFileM :: Options -> String tFile :: Options -> String tFileExe :: Options -> String agdaASTFile :: Options -> String agdaASTFileM :: Options -> String agdaParserFile :: Options -> String agdaParserFileM :: Options -> String agdaLibFile :: Options -> String agdaLibFileM :: Options -> String agdaMainFile :: Options -> String agdaMainFileM :: Options -> String noLang :: Options -> String -> String withLang :: Options -> String -> String pkgToDir :: String -> FilePath -- |
--   >>> mkMod withLang "Abstract" defaultOptions { lang = "abc" }
--   "AbstractAbc"
--   
--   >>> mkMod noLang "Abstract" defaultOptions { lang = "abc" }
--   "Abstract"
--   
--   >>> mkMod withLang "Abstract" defaultOptions { lang = "abc", inPackage = Just "A.B.C" }
--   "A.B.C.AbstractAbc"
--   
--   >>> mkMod withLang "Abstract" defaultOptions { lang = "abc", inDir = True }
--   "Abc.Abstract"
--   
--   >>> mkMod withLang "Abstract" defaultOptions { lang = "abc", inDir = True, inPackage = Just "A.B.C" }
--   "A.B.C.Abc.Abstract"
--   
mkMod :: (Options -> String -> String) -> String -> Options -> String -- |
--   >>> mkFile withLang "Abstract" "hs" defaultOptions { lang = "abc" }
--   "AbstractAbc.hs"
--   
--   >>> mkFile noLang "Abstract" "hs" defaultOptions { lang = "abc" }
--   "Abstract.hs"
--   
--   >>> mkFile withLang "Abstract" "" defaultOptions { lang = "abc" }
--   "AbstractAbc"
--   
--   >>> mkFile noLang "Abstract" "" defaultOptions { lang = "abc" }
--   "Abstract"
--   
--   >>> mkFile withLang "Abstract" "hs" defaultOptions { lang = "abc", inDir = True }
--   "Abc/Abstract.hs"
--   
--   >>> mkFile withLang "Abstract" "hs" defaultOptions { lang = "abc", inDir = True, inPackage = Just "A.B.C" }
--   "A/B/C/Abc/Abstract.hs"
--   
mkFile :: (Options -> String -> String) -> String -> String -> Options -> FilePath -- | Determine the modules' namespace -- --
--   >>> mkNamespace defaultOptions
--   ""
--   
--   >>> mkNamespace defaultOptions { lang = "Bla", inDir = True }
--   "Bla"
--   
--   >>> mkNamespace defaultOptions { inPackage = Just "My.Cool.Package" }
--   "My.Cool.Package"
--   
--   >>> mkNamespace defaultOptions { lang = "bla_bla", inDir = True }
--   "BlaBla"
--   
--   >>> mkNamespace defaultOptions { lang = "bla", inDir = True, inPackage = Just "P"}
--   "P.Bla"
--   
mkNamespace :: Options -> FilePath -- | Determine the directory corresponding to the modules' namespace -- --
--   >>> codeDir defaultOptions
--   ""
--   
--   >>> codeDir defaultOptions { lang = "Bla", inDir = True }
--   "Bla"
--   
--   >>> codeDir defaultOptions { inPackage = Just "My.Cool.Package" }
--   "My/Cool/Package"
--   
--   >>> codeDir defaultOptions { lang = "bla_bla", inDir = True }
--   "BlaBla"
--   
--   >>> codeDir defaultOptions { lang = "bla", inDir = True, inPackage = Just "P"}
--   "P/Bla"
--   
codeDir :: Options -> FilePath module BNFC.Backend.Haskell.CFtoPrinter -- | Derive pretty-printer from a BNF grammar. cf2Printer :: TokenText -> Bool -> Bool -> String -> AbsMod -> CF -> Doc -- | Define an ordering on lists' rules with the following properties: -- -- -- -- This is desiged to correctly order the rules in the prt function for -- lists so that the pattern matching works as expectd. -- --
--   >>> compareRules (npRule "[]" (ListCat (CoercCat "Foo" 3)) [] Parsable) (npRule "[]" (ListCat (CoercCat "Foo" 1)) [] Parsable)
--   LT
--   
-- --
--   >>> compareRules (npRule "[]" (ListCat (CoercCat "Foo" 3)) [] Parsable) (npRule "[]" (ListCat (Cat "Foo")) [] Parsable)
--   LT
--   
-- --
--   >>> compareRules (npRule "[]" (ListCat (Cat "Foo")) [] Parsable) (npRule "(:[])" (ListCat (Cat "Foo")) [] Parsable)
--   LT
--   
-- --
--   >>> compareRules (npRule "(:[])" (ListCat (Cat "Foo")) [] Parsable) (npRule "(:)" (ListCat (Cat "Foo")) [] Parsable)
--   LT
--   
compareRules :: IsFun f => Rul f -> Rul f -> Ordering module BNFC.Backend.OCaml.CFtoOCamlPrinter cf2Printer :: String -> ModuleName -> CF -> String prtFun :: Cat -> String module BNFC.Backend.OCaml.CFtoOCamlTest -- | OCaml comment >>> comment "I'm a comment" (* I'm a comment *) comment :: Doc -> Doc -- | Generate a test program in OCaml ocamlTestfile :: OCamlParser -> String -> String -> String -> String -> String -> CF -> Doc module BNFC.Backend.Haskell.CFtoHappy -- | Generate a happy parser file from a grammar. cf2Happy :: ModuleName -> ModuleName -> ModuleName -> HappyMode -> TokenText -> Bool -> CF -> String convert :: String -> Doc module BNFC.Backend.Haskell.CFtoAlex3 cf2alex3 :: String -> TokenText -> CF -> String instance BNFC.Backend.Haskell.CFtoAlex3.Print a => BNFC.Backend.Haskell.CFtoAlex3.Print [a] instance BNFC.Backend.Haskell.CFtoAlex3.Print GHC.Types.Char instance BNFC.Backend.Haskell.CFtoAlex3.Print BNFC.Abs.Identifier instance BNFC.Backend.Haskell.CFtoAlex3.Print BNFC.Abs.Reg instance BNFC.PrettyPrint.Pretty a => BNFC.PrettyPrint.Pretty (BNFC.Backend.Haskell.CFtoAlex3.BTree a) module BNFC.Backend.Haskell.CFtoAbstract -- | Create a Haskell module containing data type definitions for the -- abstract syntax. cf2Abstract :: SharedOptions -> String -> CF -> Doc -- | Parametrize definedRules so that it can be used for Agda as -- well. data DefCfg DefCfg :: (String -> String) -> String -> String -> String -> String -> (String -> String) -> (Exp -> Exp) -> ([Base] -> [Base]) -> DefCfg [sanitizeName] :: DefCfg -> String -> String [hasType] :: DefCfg -> String [arrow] :: DefCfg -> String [lambda] :: DefCfg -> String [cons] :: DefCfg -> String [convTok] :: DefCfg -> String -> String [convLitInt] :: DefCfg -> Exp -> Exp [polymorphism] :: DefCfg -> [Base] -> [Base] -- | Generate Haskell/Agda code for the defined constructors. definedRules' :: DefCfg -> Bool -> CF -> [Doc] -- | Generate Haskell code for the defined constructors. definedRules :: Bool -> CF -> [Doc] module BNFC.Backend.HaskellGADT.CFtoAbstractGADT cf2Abstract :: TokenText -> String -> CF -> String -> String module BNFC.Backend.C.CFtoFlexC -- | Entrypoint. cf2flex :: ParserMode -> CF -> (String, SymMap) data ParserMode -- | C (False) or C++ no STL (True) -- mode, with name to use as prefix. CParser :: Bool -> String -> ParserMode -- | C++ mode, with optional package name CppParser :: InPackage -> String -> ParserMode parserName :: ParserMode -> String parserPackage :: ParserMode -> InPackage cParser :: ParserMode -> Bool stlParser :: ParserMode -> Bool parserHExt :: ParserMode -> String -- | Part of the lexer prelude needed when string literals are to be lexed. -- Defines an interface to the Buffer. preludeForBuffer :: String -> [String] cMacros :: CF -> String -- | If we have several block comments, we need different COMMENT lexing -- states. commentStates :: [String] -- | Create flex rules for single-line and multi-lines comments. The first -- argument is an optional namespace (for C++); the second argument is -- the set of comment delimiters as returned by BNFC.CF.comments. -- -- This function is only compiling the results of applying either -- lexSingleComment or lexMultiComment on each comment delimiter or pair -- of delimiters. -- --
--   >>> lexComments ([("{-","-}")],["--"])
--   <INITIAL>"--"[^\n]* /* skip */; /* BNFC: comment "--" */
--   <INITIAL>"{-" BEGIN COMMENT; /* BNFC: block comment "{-" "-}" */
--   <COMMENT>"-}" BEGIN INITIAL;
--   <COMMENT>.    /* skip */;
--   <COMMENT>[\n] /* skip */;
--   
lexComments :: ([(String, String)], [String]) -> Doc -- | Lexing of strings, converting escaped characters. lexStrings :: String -> String -> String -> [String] -- | Lexing of characters, converting escaped characters. lexChars :: String -> String -> [String] module BNFC.Backend.Java.CFtoJLex15 -- | The environment is returned for further use in the parser. cf2jlex :: JavaLexerParser -> RecordPositions -> String -> CF -> (Doc, SymEnv) module BNFC.Backend.C.CFtoCAbs -- | The result is two files (.H file, .C file) cf2CAbs :: RecordPositions -> String -> CF -> (String, String) module BNFC.Backend.C.CFtoBisonC cf2Bison :: RecordPositions -> ParserMode -> CF -> SymMap -> String resultName :: String -> String typeName :: String -> String -- | slightly stronger than the NamedVariable version. >>> varName -- (Cat Abc) "abc_" varName :: Cat -> String -- | Produces a table with the built-in token types. specialToks :: CF -> [[String]] -- | Bison only supports a single entrypoint. startSymbol :: CF -> String unionBuiltinTokens :: [String] -- | Backend base module. -- -- Defines the type of the backend and some useful functions. module BNFC.Backend.Base type Backend = MkFiles () -- | Define the type of the backend functions. For more purity, instead of -- having each backend writing the generated files to disk, they return a -- list of pairs containing the (relative) file path and the file -- content. This allow for 1) easier testing, 2) implement common options -- like changing the output dir or providing a diff instead of -- overwritting the files on a highter level and 3) more purity. -- -- The writer monad provides a more convenient API to generate the list. -- Note that we still use the IO monad for now because some -- backends insist on printing stuff to the screen while generating the -- files. type MkFiles a = WriterT [GeneratedFile] IO a -- | A result file of a backend. data GeneratedFile GeneratedFile :: FilePath -> MakeComment -> String -> GeneratedFile -- | Name of the file to write. [fileName] :: GeneratedFile -> FilePath -- | Function to generate a comment. Used to prefix the file with a stamp -- ("Generated by BNFC"). [makeComment] :: GeneratedFile -> MakeComment -- | Content of the file to write. [fileContent] :: GeneratedFile -> String -- | Type of comment-generating functions. type MakeComment = String -> String -- | Named after execWriter, this function execute the given backend and -- returns the generated file paths and contents. execBackend :: MkFiles () -> IO [GeneratedFile] -- | A specialized version of tell that adds a file and its content -- to the list of generated files. mkfile :: FileContent c => FilePath -> MakeComment -> c -> MkFiles () -- | Lift a computation from the IO monad. liftIO :: MonadIO m => IO a -> m a -- | Write a set of files to disk. the first argument is the root directory -- inside which all the generated files will be written. This root -- directory and sub-directories will be created as needed (ex: if the -- files contains a a/b/file.txt, writeFiles will create -- the directories $ROOT/a and $ROOT/a/b) writeFiles :: FilePath -> MkFiles () -> IO () instance BNFC.Backend.Base.FileContent [GHC.Types.Char] instance BNFC.Backend.Base.FileContent Text.PrettyPrint.HughesPJ.Doc instance GHC.Show.Show BNFC.Backend.Base.GeneratedFile instance GHC.Classes.Eq BNFC.Backend.Base.GeneratedFile module BNFC.Backend.XML type Coding = Bool makeXML :: SharedOptions -> Coding -> CF -> Backend cf2DTD :: Coding -> String -> CF -> String comment :: String -> String -- |
--   >>> tag "test"
--   "<test>"
--   
tag :: String -> String element :: String -> [String] -> String attlist :: [Char] -> [Char] -> String elemAtt :: String -> [Char] -> [String] -> String elemt :: String -> [String] -> String elemc :: Cat -> [(Fun, String)] -> String elemEmp :: String -> String alts :: [String] -> String elemData :: Bool -> CF -> (Cat, [(Fun, [Cat])]) -> String efunDef :: Bool -> String endtagDef :: Bool -> String elemDataConstrs :: CF -> (Cat, [(Fun, [Cat])]) -> String efunDefConstrs :: String endtagDefConstrs :: String elemDataConstr :: CF -> (Cat, [(Fun, [Cat])]) -> String efunDefConstr :: String endtagDefConstr :: String elemDataNotyp :: CF -> (a, [(String, [Cat])]) -> String efunDefNotyp :: String endtagDefNotyp :: String rhsCat :: CF -> Fun -> [Cat] -> String rhsCatNot :: CF -> [Cat] -> [Char] symbCat :: CF -> Cat -> Doc symbCatNot :: CF -> Cat -> Doc parenth :: [Char] -> [Char] cf2XMLPrinter :: Bool -> SharedOptions -> String -> CF -> String pragmas :: SharedOptions -> String prologue :: Bool -> SharedOptions -> String -> String integerRule :: p -> String doubleRule :: p -> String stringRule :: p -> String showsPrintRule :: p -> [Char] -> String identRule :: CF -> String ownPrintRule :: CF -> TokenCat -> String rules :: CF -> String case_fun :: Cat -> [(String, [String])] -> String module BNFC.Backend.Pygments makePygments :: SharedOptions -> CF -> Backend comment :: String -> String setup :: String -> Doc lexer :: String -> CF -> Doc -- | Convert a Reg to a python regex >>> pyRegex (RSeqs "abc") abc -- >>> pyRegex (RAlt (RSeqs "::=") (RChar .)) ::=|. -- >>> pyRegex (RChar '=') = >>> pyRegex RAny . -- >>> pyRegex (RStar RAny) .* >>> pyRegex (RPlus -- (RSeqs "xxx")) (xxx)+ >>> pyRegex (ROpt (RSeqs "abc")) (abc)? -- >>> pyRegex (RSeq (RSeqs "--") (RSeq (RStar RAny) (RChar -- 'n'))) --.*n >>> pyRegex (RStar (RSeq (RSeqs "abc") (RChar -- *))) (abc*)* >>> pyRegex REps BLANKLINE -- >>> pyRegex (RAlts "abc[].") [abc[].] >>> pyRegex -- RDigit d >>> pyRegex RLetter [a-zA-Z] >>> pyRegex -- RUpper [A-Z] >>> pyRegex RLower [a-z] >>> pyRegex -- (RMinus RAny RDigit) (.)(?<!d) >>> pyRegex (RSeq (RAlt -- (RChar a) RAny) (RAlt (RChar b) (RChar c))) -- (a|.)(b|c) pyRegex :: Reg -> Doc module BNFC.Backend.Common.Makefile -- | Creates a Makefile rule. -- --
--   >>> mkRule "main" ["file1","file2"] ["do something"]
--   main : file1 file2
--   	do something
--   
-- --
--   >>> mkRule "main" ["program.exe"] []
--   main : program.exe
--   
mkRule :: String -> [String] -> [String] -> Doc -- | Variable assignment. -- --
--   >>> mkVar "FOO" "bar"
--   FOO=bar
--   
mkVar :: String -> String -> Doc -- | Variable referencing. -- --
--   >>> refVar "FOO"
--   "${FOO}"
--   
refVar :: String -> String -- | Create the Makefile file using the name specified in the option -- record. mkMakefile :: SharedOptions -> (String -> Doc) -> Backend module BNFC.Backend.Latex -- | Entry point: create .tex file and a Makefile to compile it. makeLatex :: SharedOptions -> CF -> Backend -- | Create a makefile for the given tex file -- --
--   >>> makefile "myFile.tex" "Makefile"
--   all : myFile.pdf
--   
--   myFile.pdf : myFile.tex
--   	pdflatex myFile.tex
--   
--   clean :
--   	-rm myFile.pdf myFile.aux myFile.log
--   
--   cleanall : clean
--   	-rm Makefile myFile.tex
--   
makefile :: String -> String -> Doc comment :: String -> String -- | Create content of .tex file. cfToLatex :: String -> CF -> String introduction :: String prtTerminals :: String -> CF -> String identSection :: CF -> [String] prtIdentifiers :: [String] prtLiterals :: String -> CF -> String stringLit :: TokenCat -> [String] prtOwnToken :: (String, Reg) -> String prtComments :: ([(String, String)], [String]) -> String prtSymb :: String -> CF -> String prtReserved :: String -> CF -> String stringRes :: String -> String -- | Group a list into blocks of 3 elements. three :: Monoid a => [a] -> [[a]] prtBNF :: String -> CF -> String prtRules :: [(Cat, [Rule])] -> String prtSymbols :: [Either Cat String] -> String prt :: String -> String macros :: String reserved :: String -> String literal :: String -> String empty :: String symbol :: String -> String tabular :: Int -> [[String]] -> String terminal :: String -> String nonterminal :: Cat -> String arrow :: String delimiter :: String beginDocument :: String -> String endDocument :: String latexRegExp :: Reg -> String -- | Top-level for the Java back end. -- --
--   $Id: JavaTop15.hs,v 1.12 2007/01/08 18:20:23 aarne Exp $
--   
module BNFC.Backend.Java -- | Build the Java output. -- -- This creates the Java files. makeJava :: SharedOptions -> CF -> MkFiles () module BNFC.Backend.CPP.Makefile makefile :: String -> String -> String -> Doc module BNFC.Backend.C makeC :: SharedOptions -> CF -> MkFiles () -- | A tiny buffer library for string buffers in the lexer. bufferC :: String -> String -- | A tiny buffer library for string buffers in the lexer. bufferH :: String -- | Put string into a block comment. comment :: String -> String -- | A heading comment for the generated parser test. testfileHeader :: [String] module BNFC.Backend.OCaml makeOCaml :: SharedOptions -> CF -> MkFiles () -- | Common to the C++ backends. module BNFC.Backend.CPP.Common -- | C++ line comment including mode hint for emacs. commentWithEmacsModeHint :: String -> String -- | C++ code for the defined constructors. -- -- definedRules Nothing only prints the header. definedRules :: Maybe ListConstructors -> CF -> String -> String module BNFC.Backend.CPP.STL.CFtoSTLAbs cf2CPPAbs :: RecordPositions -> Maybe String -> String -> CF -> (String, String) module BNFC.Backend.CPP.STL makeCppStl :: SharedOptions -> CF -> MkFiles () module BNFC.Backend.CPP.NoSTL.CFtoCPPAbs cf2CPPAbs :: String -> CF -> (String, String) module BNFC.Backend.CPP.NoSTL makeCppNoStl :: SharedOptions -> CF -> MkFiles () -- | Agda backend. -- -- Generate bindings to Haskell data types for use in Agda. -- -- Example for abstract syntax generated in Haskell backend: -- --
--   module CPP.Abs where
--   
--   import Prelude (Char, Double, Integer, String)
--   import qualified Prelude as C (Eq, Ord, Show, Read)
--   
--   import qualified Data.Text
--   
--   newtype Ident = Ident Data.Text.Text
--     deriving (C.Eq, C.Ord, C.Show, C.Read)
--   
--   data Def = DFun Type Ident [Arg] [Stm]
--     deriving (C.Eq, C.Ord, C.Show, C.Read)
--   
--   data Arg = ADecl Type Ident
--     deriving (C.Eq, C.Ord, C.Show, C.Read)
--   
--   data Stm
--       = SExp Exp
--       | SInit Type Ident Exp
--       | SBlock [Stm]
--       | SIfElse Exp Stm Stm
--     deriving (C.Eq, C.Ord, C.Show, C.Read)
--   
--   data Exp
--   
--   data Type = Type_bool | Type_int | Type_double | Type_void
--     deriving (C.Eq, C.Ord, C.Show, C.Read)
--   
-- -- This should be accompanied by the following Agda code: -- --
--   module CPP.AST where
--   
--   open import Agda.Builtin.Char using () renaming (Char to Char)
--   open import Agda.Builtin.Float public using () renaming (Float to Double)
--   open import Agda.Builtin.Int   public using () renaming (Int to Integer)
--   open import Agda.Builtin.List using () renaming (List to #List)
--   open import Agda.Builtin.String using () renaming
--     ( String to #String
--     ; primStringFromList to #stringFromList
--     )
--   
--   {-# FOREIGN GHC import Prelude (Char, Double, Integer, String) #-}
--   {-# FOREIGN GHC import qualified Data.Text #-}
--   {-# FOREIGN GHC import qualified CPP.Abs #-}
--   {-# FOREIGN GHC import CPP.Print (printTree) #-}
--   
--   data Ident : Set where
--     ident : #String → Ident
--   
--   {-# COMPILE GHC Ident = data CPP.Abs.Ident (CPP.Abs.Ident) #-}
--   
--   data Def : Set where
--     dFun : (t : Type) (x : Ident) (as : List Arg) (ss : List Stm) → Def
--   
--   {-# COMPILE GHC Def = data CPP.Abs.Def (CPP.Abs.DFun) #-}
--   
--   data Arg : Set where
--     aDecl : (t : Type) (x : Ident) → Arg
--   
--   {-# COMPILE GHC Arg = data CPP.Abs.Arg (CPP.Abs.ADecl) #-}
--   
--   data Stm : Set where
--     sExp : (e : Exp) → Stm
--     sInit : (t : Type) (x : Ident) (e : Exp) → Stm
--     sBlock : (ss : List Stm) → Stm
--     sIfElse : (e : Exp) (s s' : Stm) → Stm
--   
--   {-# COMPILE GHC Stm = data CPP.Abs.Stm
--     ( CPP.Abs.SExp
--     | CPP.Abs.SInit
--     | CPP.Abs.SBlock
--     | CPP.Abs.SIfElse
--     ) #-}
--   
--   data Type : Set where
--     typeBool typeInt typeDouble typeVoid : Type
--   
--   {-# COMPILE GHC Type = data CPP.Abs.Type
--     ( CPP.Abs.Type_bool
--     | CPP.Abs.Type_int
--     | CPP.Abs.Type_double
--     | CPP.Abs.Type_void
--     ) #-}
--   
--   -- Binding the BNFC pretty printers.
--   
--   printIdent  : Ident → String
--   printIdent (ident s) = String.fromList s
--   
--   postulate
--     printType    : Type    → String
--     printExp     : Exp     → String
--     printStm     : Stm     → String
--     printArg     : Arg     → String
--     printDef     : Def     → String
--     printProgram : Program → String
--   
--   {-# COMPILE GHC printType    = \ t -> Data.Text.pack (printTree (t :: CPP.Abs.Type)) #-}
--   {-# COMPILE GHC printExp     = \ e -> Data.Text.pack (printTree (e :: CPP.Abs.Exp))  #-}
--   {-# COMPILE GHC printStm     = \ s -> Data.Text.pack (printTree (s :: CPP.Abs.Stm))  #-}
--   {-# COMPILE GHC printArg     = \ a -> Data.Text.pack (printTree (a :: CPP.Abs.Arg))  #-}
--   {-# COMPILE GHC printDef     = \ d -> Data.Text.pack (printTree (d :: CPP.Abs.Def))  #-}
--   {-# COMPILE GHC printProgram = \ p -> Data.Text.pack (printTree (p :: CPP.Abs.Program)) #-}
--   
module BNFC.Backend.Agda -- | Entry-point for Agda backend. makeAgda :: String -> SharedOptions -> CF -> Backend instance GHC.Classes.Eq BNFC.Backend.Agda.ImportNumeric module BNFC.Backend.Haskell -- | Entrypoint for the Haskell backend. makeHaskell :: SharedOptions -> CF -> Backend -- | Which version of Alex is targeted? data AlexVersion Alex3 :: AlexVersion -- | Generate the makefile. makefile :: Options -> CF -> String -> Doc testfile :: Options -> CF -> String module BNFC.Backend.HaskellGADT makeHaskellGadt :: SharedOptions -> CF -> MkFiles ()