-- 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 BNFC3 @version 3.0 -- | The abstract syntax of language BNFC. module BNFC.Abs type Grammar = Grammar' BNFC'Position data Grammar' a Grammar :: a -> [Def' a] -> Grammar' a type Def = Def' BNFC'Position data Def' a Rule :: a -> Label' a -> Cat' a -> RHS' a -> Def' a Comment :: a -> String -> Def' a Comments :: a -> String -> String -> Def' a Internal :: a -> Label' a -> Cat' a -> RHS' a -> Def' a Token :: a -> Identifier -> Reg' a -> Def' a PosToken :: a -> Identifier -> Reg' a -> Def' a Entryp :: a -> [Cat' a] -> Def' a Separator :: a -> MinimumSize' a -> Cat' a -> String -> Def' a Terminator :: a -> MinimumSize' a -> Cat' a -> String -> Def' a Delimiters :: a -> Cat' a -> String -> String -> Separation' a -> MinimumSize' a -> Def' a Coercions :: a -> Identifier -> Integer -> Def' a Rules :: a -> Identifier -> [RHS' a] -> Def' a Function :: a -> Identifier -> [Arg' a] -> Exp' a -> Def' a Layout :: a -> [String] -> Def' a LayoutStop :: a -> [String] -> Def' a LayoutTop :: a -> Def' a type Item = Item' BNFC'Position data Item' a Terminal :: a -> String -> Item' a NTerminal :: a -> Cat' a -> Item' a type Cat = Cat' BNFC'Position data Cat' a ListCat :: a -> Cat' a -> Cat' a IdCat :: a -> Identifier -> Cat' a type Label = Label' BNFC'Position data Label' a Id :: a -> Identifier -> Label' a Wild :: a -> Label' a ListEmpty :: a -> Label' a ListCons :: a -> Label' a ListOne :: a -> Label' a type Arg = Arg' BNFC'Position data Arg' a Arg :: a -> Identifier -> Arg' a type Separation = Separation' BNFC'Position data Separation' a SepNone :: a -> Separation' a SepTerm :: a -> String -> Separation' a SepSepar :: a -> String -> Separation' a type Exp = Exp' BNFC'Position data Exp' a Cons :: a -> Exp' a -> Exp' a -> Exp' a App :: a -> Identifier -> [Exp' a] -> Exp' a Var :: a -> Identifier -> Exp' a LitInteger :: a -> Integer -> Exp' a LitChar :: a -> Char -> Exp' a LitString :: a -> String -> Exp' a LitDouble :: a -> Double -> Exp' a List :: a -> [Exp' a] -> Exp' a type RHS = RHS' BNFC'Position data RHS' a RHS :: a -> [Item' a] -> RHS' a type MinimumSize = MinimumSize' BNFC'Position data MinimumSize' a MNonEmpty :: a -> MinimumSize' a MEmpty :: a -> MinimumSize' a type Reg = Reg' BNFC'Position data Reg' a RAlt :: a -> Reg' a -> Reg' a -> Reg' a RMinus :: a -> Reg' a -> Reg' a -> Reg' a RSeq :: a -> Reg' a -> Reg' a -> Reg' a RStar :: a -> Reg' a -> Reg' a RPlus :: a -> Reg' a -> Reg' a ROpt :: a -> Reg' a -> Reg' a REps :: a -> Reg' a RChar :: a -> Char -> Reg' a RAlts :: a -> String -> Reg' a RSeqs :: a -> String -> Reg' a RDigit :: a -> Reg' a RLetter :: a -> Reg' a RUpper :: a -> Reg' a RLower :: a -> Reg' a RAny :: a -> Reg' a 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 Data.Traversable.Traversable BNFC.Abs.Separation' instance Data.Foldable.Foldable BNFC.Abs.Separation' instance GHC.Base.Functor BNFC.Abs.Separation' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Separation' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Separation' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Separation' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Separation' a) instance Data.Traversable.Traversable BNFC.Abs.MinimumSize' instance Data.Foldable.Foldable BNFC.Abs.MinimumSize' instance GHC.Base.Functor BNFC.Abs.MinimumSize' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.MinimumSize' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.MinimumSize' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.MinimumSize' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.MinimumSize' a) instance Data.Traversable.Traversable BNFC.Abs.Reg' instance Data.Foldable.Foldable BNFC.Abs.Reg' instance GHC.Base.Functor BNFC.Abs.Reg' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Reg' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Reg' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Reg' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Reg' a) 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 Data.Traversable.Traversable BNFC.Abs.Exp' instance Data.Foldable.Foldable BNFC.Abs.Exp' instance GHC.Base.Functor BNFC.Abs.Exp' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Exp' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Exp' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Exp' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Exp' a) instance Data.Traversable.Traversable BNFC.Abs.Arg' instance Data.Foldable.Foldable BNFC.Abs.Arg' instance GHC.Base.Functor BNFC.Abs.Arg' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Arg' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Arg' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Arg' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Arg' a) instance Data.Traversable.Traversable BNFC.Abs.Label' instance Data.Foldable.Foldable BNFC.Abs.Label' instance GHC.Base.Functor BNFC.Abs.Label' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Label' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Label' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Label' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Label' a) instance Data.Traversable.Traversable BNFC.Abs.Cat' instance Data.Foldable.Foldable BNFC.Abs.Cat' instance GHC.Base.Functor BNFC.Abs.Cat' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Cat' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Cat' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Cat' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Cat' a) instance Data.Traversable.Traversable BNFC.Abs.Item' instance Data.Foldable.Foldable BNFC.Abs.Item' instance GHC.Base.Functor BNFC.Abs.Item' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Item' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Item' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Item' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Item' a) instance Data.Traversable.Traversable BNFC.Abs.RHS' instance Data.Foldable.Foldable BNFC.Abs.RHS' instance GHC.Base.Functor BNFC.Abs.RHS' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.RHS' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.RHS' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.RHS' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.RHS' a) instance Data.Traversable.Traversable BNFC.Abs.Def' instance Data.Foldable.Foldable BNFC.Abs.Def' instance GHC.Base.Functor BNFC.Abs.Def' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Def' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Def' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Def' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Def' a) instance Data.Traversable.Traversable BNFC.Abs.Grammar' instance Data.Foldable.Foldable BNFC.Abs.Grammar' instance GHC.Base.Functor BNFC.Abs.Grammar' instance GHC.Read.Read a => GHC.Read.Read (BNFC.Abs.Grammar' a) instance GHC.Show.Show a => GHC.Show.Show (BNFC.Abs.Grammar' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Abs.Grammar' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Abs.Grammar' a) instance BNFC.Abs.HasPosition BNFC.Abs.Grammar instance BNFC.Abs.HasPosition BNFC.Abs.Def instance BNFC.Abs.HasPosition BNFC.Abs.Item instance BNFC.Abs.HasPosition BNFC.Abs.Cat instance BNFC.Abs.HasPosition BNFC.Abs.Label instance BNFC.Abs.HasPosition BNFC.Abs.Arg instance BNFC.Abs.HasPosition BNFC.Abs.Separation instance BNFC.Abs.HasPosition BNFC.Abs.Exp instance BNFC.Abs.HasPosition BNFC.Abs.RHS instance BNFC.Abs.HasPosition BNFC.Abs.MinimumSize instance BNFC.Abs.HasPosition BNFC.Abs.Reg instance BNFC.Abs.HasPosition BNFC.Abs.Identifier module BNFC.Backend.Common.Xml module BNFC.Backend.CommonInterface.Makefile 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) 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 data AlexAddr AlexA# :: Addr# -> AlexAddr alexIndexInt16OffAddr :: AlexAddr -> Int# -> Int# 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 -- | Pretty-printer for BNFC. Generated by the BNF converter. 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' a) instance BNFC.Print.Print [BNFC.Abs.Def' a] instance BNFC.Print.Print (BNFC.Abs.Def' a) instance BNFC.Print.Print (BNFC.Abs.Item' a) instance BNFC.Print.Print [BNFC.Abs.Item' a] instance BNFC.Print.Print (BNFC.Abs.Cat' a) instance BNFC.Print.Print [BNFC.Abs.Cat' a] instance BNFC.Print.Print (BNFC.Abs.Label' a) instance BNFC.Print.Print (BNFC.Abs.Arg' a) instance BNFC.Print.Print [BNFC.Abs.Arg' a] instance BNFC.Print.Print (BNFC.Abs.Separation' a) instance BNFC.Print.Print [GHC.Base.String] instance BNFC.Print.Print (BNFC.Abs.Exp' a) instance BNFC.Print.Print [BNFC.Abs.Exp' a] instance BNFC.Print.Print (BNFC.Abs.RHS' a) instance BNFC.Print.Print [BNFC.Abs.RHS' a] instance BNFC.Print.Print (BNFC.Abs.MinimumSize' a) instance BNFC.Print.Print (BNFC.Abs.Reg' a) module BNFC.Utils.Decoration -- | A decoration is a functor that is traversable into any functor. -- -- The Functor superclass is given because of the limitations of -- the Haskell class system. traverseF actually implies -- functoriality. -- -- Minimal complete definition: traverseF or -- distributeF. class Functor t => Decoration t -- | traverseF is the defining property. traverseF :: (Decoration t, Functor m) => (a -> m b) -> t a -> m (t b) -- | Decorations commute into any functor. distributeF :: (Decoration t, Functor m) => t (m a) -> m (t a) traverseF2 :: (Decoration t, Bifunctor m) => (a -> m b c) -> t a -> m (t b) (t c) -- | Decorations commute into any bifunctor. distributeF2 :: (Decoration t, Bifunctor m) => t (m a b) -> m (t a) (t b) -- | Any decoration is traversable with traverse = traverseF. Just -- like any Traversable is a functor, so is any decoration, given -- by just traverseF, a functor. dmap :: Decoration t => (a -> b) -> t a -> t b -- | Any decoration is a lens. set is a special case of -- dmap. dget :: Decoration t => t a -> a -- | A proper name for a generic decoration. data DecorationT d a DecorationT :: d -> a -> DecorationT d a [decoration] :: DecorationT d a -> d [decorated] :: DecorationT d a -> a instance Data.Traversable.Traversable (BNFC.Utils.Decoration.DecorationT d) instance Data.Foldable.Foldable (BNFC.Utils.Decoration.DecorationT d) instance GHC.Base.Functor (BNFC.Utils.Decoration.DecorationT d) instance (GHC.Show.Show d, GHC.Show.Show a) => GHC.Show.Show (BNFC.Utils.Decoration.DecorationT d a) instance (GHC.Classes.Ord d, GHC.Classes.Ord a) => GHC.Classes.Ord (BNFC.Utils.Decoration.DecorationT d a) instance (GHC.Classes.Eq d, GHC.Classes.Eq a) => GHC.Classes.Eq (BNFC.Utils.Decoration.DecorationT d a) instance BNFC.Utils.Decoration.Decoration (BNFC.Utils.Decoration.DecorationT d) instance BNFC.Utils.Decoration.Decoration Data.Functor.Identity.Identity instance (BNFC.Utils.Decoration.Decoration d, BNFC.Utils.Decoration.Decoration t) => BNFC.Utils.Decoration.Decoration (Data.Functor.Compose.Compose d t) instance BNFC.Utils.Decoration.Decoration ((,) a) -- | Non-empty lists. -- -- Better name List1 for non-empty lists, plus missing -- functionality. -- -- Import: @ -- -- {-# LANGUAGE PatternSynonyms #-} -- -- import BNFC.Utils.List1 (List1, pattern (:|)) import qualified -- BNFC.Utils.List1 as List1 -- -- @ module BNFC.Utils.List1 -- | Non-empty String. type String1 = List1 Char -- | Non-empty list. TODO change to newtype? type List1 = NonEmpty trim1 :: String -> Maybe String1 -- | Return the last element and the rest. initLast :: List1 a -> ([a], a) -- | Build a list with one element. singleton :: a -> List1 a -- | Append a list to a non-empty list. appendList :: List1 a -> [a] -> List1 a -- | Prepend a list to a non-empty list. prependList :: [a] -> List1 a -> List1 a -- | More precise type for snoc. snoc :: [a] -> a -> List1 a -- | Concatenate one or more non-empty lists. concat :: [List1 a] -> [a] -- | Like union. Duplicates in the first list are not removed. -- O(nm). union :: Eq a => List1 a -> List1 a -> List1 a ifNull :: [a] -> b -> (List1 a -> b) -> b ifNotNull :: [a] -> (List1 a -> b) -> b -> b -- | Checks if all the elements in the list are equal. Assumes that the -- Eq instance stands for an equivalence relation. O(n). allEqual :: Eq a => List1 a -> Bool -- | Like catMaybes. catMaybes :: List1 (Maybe a) -> [a] -- | Like filter. mapMaybe :: (a -> Maybe b) -> List1 a -> [b] -- | Like partitionEithers. partitionEithers :: List1 (Either a b) -> ([a], [b]) -- | Like lefts. lefts :: List1 (Either a b) -> [a] -- | Like rights. rights :: List1 (Either a b) -> [b] -- | Like zipWithM. zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) -- | Like zipWithM. zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m () -- | sortWith for NonEmpty, behaves the same as: -- --
-- sortBy . comparing --sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a -- | sortBy for NonEmpty, behaves the same as sortBy sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a -- | transpose for NonEmpty, behaves the same as -- transpose The rows/columns need not be the same length, in -- which case > transpose . transpose /= id transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a) -- | The nubBy function behaves just like nub, except it uses -- a user-supplied equality predicate instead of the overloaded == -- function. nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a -- | The nub function removes duplicate elements from a list. In -- particular, it keeps only the first occurrence of each element. (The -- name nub means 'essence'.) It is a special case of -- nubBy, which allows the programmer to supply their own -- inequality test. nub :: Eq a => NonEmpty a -> NonEmpty a -- | The unzip function is the inverse of the zip function. unzip :: Functor f => f (a, b) -> (f a, f b) -- | The zipWith function generalizes zip. Rather than -- tupling the elements, the elements are combined using the function -- passed as the first argument. zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c -- | The zip function takes two streams and returns a stream of -- corresponding pairs. zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) -- | xs !! n returns the element of the stream xs at -- index n. Note that the head of the stream has index 0. -- -- Beware: a negative or out-of-bounds index will cause an error. (!!) :: NonEmpty a -> Int -> a infixl 9 !! -- | The isPrefixOf function returns True if the first -- argument is a prefix of the second. isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool -- | groupAllWith1 is to groupWith1 as groupAllWith is -- to groupWith groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupWith1 is to group1 as groupWith is to -- group groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupBy1 is to group1 as groupBy is to -- group. groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | group1 operates like group, but uses the knowledge that -- its input is non-empty to produce guaranteed non-empty output. group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a) -- | groupAllWith operates like groupWith, but sorts the list -- first so that each equivalence class has, at most, one list in the -- output groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] -- | groupWith operates like group, but uses the provided -- projection when comparing for equality groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a] -- | groupBy operates like group, but uses the provided -- equality predicate instead of ==. groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a] -- | The group function takes a stream and returns a list of streams -- such that flattening the resulting list is equal to the argument. -- Moreover, each stream in the resulting list contains only equal -- elements. For example, in list notation: -- --
-- 'group' $ 'cycle' "Mississippi" -- = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ... --group :: (Foldable f, Eq a) => f a -> [NonEmpty a] -- | The partition function takes a predicate p and a -- stream xs, and returns a pair of lists. The first list -- corresponds to the elements of xs for which p holds; -- the second corresponds to the elements of xs for which -- p does not hold. -- --
-- 'partition' p xs = ('filter' p xs, 'filter' (not . p) xs) --partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | filter p xs removes any elements from xs that -- do not satisfy p. filter :: (a -> Bool) -> NonEmpty a -> [a] -- | The break p function is equivalent to span -- (not . p). break :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | span p xs returns the longest prefix of xs -- that satisfies p, together with the remainder of the stream. -- --
-- 'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs) -- xs == ys ++ zs where (ys, zs) = 'span' p xs --span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | takeWhile p xs returns the longest prefix of the -- stream xs for which the predicate p holds. takeWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | splitAt n xs returns a pair consisting of the prefix -- of xs of length n and the remaining stream -- immediately following this prefix. -- --
-- 'splitAt' n xs == ('take' n xs, 'drop' n xs) -- xs == ys ++ zs where (ys, zs) = 'splitAt' n xs --splitAt :: Int -> NonEmpty a -> ([a], [a]) -- | drop n xs drops the first n elements off the -- front of the sequence xs. drop :: Int -> NonEmpty a -> [a] -- | take n xs returns the first n elements of -- xs. take :: Int -> NonEmpty a -> [a] -- | repeat x returns a constant stream, where all elements -- are equal to x. repeat :: a -> NonEmpty a -- | reverse a finite NonEmpty stream. reverse :: NonEmpty a -> NonEmpty a -- | cycle xs returns the infinite repetition of -- xs: -- --
-- cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...] --cycle :: NonEmpty a -> NonEmpty a -- | iterate f x produces the infinite sequence of repeated -- applications of f to x. -- --
-- iterate f x = x :| [f x, f (f x), ..] --iterate :: (a -> a) -> a -> NonEmpty a -- | 'intersperse x xs' alternates elements of the list with copies of -- x. -- --
-- intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3] --intersperse :: a -> NonEmpty a -> NonEmpty a -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
-- scanl1 f [x1, x2, ...] == x1 :| [x1 `f` x2, x1 `f` (x2 `f` x3), ...] --scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a -- | scanr is the right-to-left dual of scanl. Note that -- --
-- head (scanr f z xs) == foldr f z xs. --scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b -- | scanl is similar to foldl, but returns a stream of -- successive reduced values from the left: -- --
-- scanl f z [x1, x2, ...] == z :| [z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b -- | some1 x sequences x one or more times. some1 :: Alternative f => f a -> f (NonEmpty a) -- | insert x xs inserts x into the last position -- in xs where it is still less than or equal to the next -- element. In particular, if the list is sorted beforehand, the result -- will also be sorted. insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a -- | The tails function takes a stream xs and returns all -- the suffixes of xs. tails :: Foldable f => f a -> NonEmpty [a] -- | The inits function takes a stream xs and returns all -- the finite prefixes of xs. inits :: Foldable f => f a -> NonEmpty [a] -- | Map a function over a NonEmpty stream. map :: (a -> b) -> NonEmpty a -> NonEmpty b -- | Convert a stream to a normal list efficiently. toList :: NonEmpty a -> [a] -- | Converts a normal list to a NonEmpty stream. -- -- Raises an error if given an empty list. fromList :: [a] -> NonEmpty a -- | Sort a stream. sort :: Ord a => NonEmpty a -> NonEmpty a -- | Synonym for <|. cons :: a -> NonEmpty a -> NonEmpty a -- | Prepend an element to the stream. (<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 <| -- | Extract everything except the last element of the stream. init :: NonEmpty a -> [a] -- | Extract the last element of the stream. last :: NonEmpty a -> a -- | Extract the possibly-empty tail of the stream. tail :: NonEmpty a -> [a] -- | Extract the first element of the stream. head :: NonEmpty a -> a -- | The unfoldr function is analogous to Data.List's -- unfoldr operation. unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b -- | uncons produces the first element of the stream, and a stream -- of the remaining elements, if any. uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) -- | nonEmpty efficiently turns a normal list into a NonEmpty -- stream, producing Nothing if the input is empty. nonEmpty :: [a] -> Maybe (NonEmpty a) -- | unfold produces a new stream by repeatedly applying the -- unfolding function to the seed value to produce an element of type -- b and a new seed value. When the unfolding function returns -- Nothing instead of a new seed value, the stream ends. unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b -- | Compute n-ary logic exclusive OR operation on NonEmpty list. xor :: NonEmpty Bool -> Bool -- | Number of elements in NonEmpty list. length :: NonEmpty a -> Int pattern (:|) :: () => a -> [a] -> NonEmpty a infixr 5 :| instance Data.String.IsString BNFC.Utils.List1.String1 -- | Lists of length at least 2. -- -- Import as: import BNFC.Utils.List2 (List2(List2)) import -- qualified BNFC.Utils.List2 as List2 module BNFC.Utils.List2 -- | Lists of length ≥2. data List2 a List2 :: a -> a -> [a] -> List2 a type List1 = NonEmpty cons :: a -> List2 a -> List2 a snoc :: List2 a -> a -> List2 a -- | Safe. head :: List2 a -> a -- | Safe. tail :: List2 a -> [a] -- | Safe. tail1 :: List2 a -> List1 a toList1 :: List2 a -> List1 a -- | Unsafe! fromList :: [a] -> List2 a -- | Unsafe! fromList1 :: List1 a -> List2 a break :: (a -> Bool) -> List2 a -> ([a], [a]) -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: IsList l => l -> [Item l] instance Data.Traversable.Traversable BNFC.Utils.List2.List2 instance Data.Foldable.Foldable BNFC.Utils.List2.List2 instance GHC.Base.Functor BNFC.Utils.List2.List2 instance GHC.Show.Show a => GHC.Show.Show (BNFC.Utils.List2.List2 a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Utils.List2.List2 a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Utils.List2.List2 a) instance GHC.Base.Semigroup (BNFC.Utils.List2.List2 a) instance GHC.Exts.IsList (BNFC.Utils.List2.List2 a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (BNFC.Utils.List2.List2 a) module BNFC.Utils.Panic panic :: HasCallStack => String -> a panicPositionNothing :: HasCallStack => a panicEmptyIdentifier :: HasCallStack => a -- | Constructing singleton collections. module BNFC.Utils.Singleton -- | A create-only possibly empty collection is a monoid with the -- possibility to inject elements. class (Semigroup coll, Monoid coll, Singleton el coll) => Collection el coll | coll -> el fromList :: Collection el coll => [el] -> coll -- | Overloaded singleton constructor for collections. class Singleton el coll | coll -> el singleton :: Singleton el coll => el -> coll instance BNFC.Utils.Singleton.Collection a [a] instance BNFC.Utils.Singleton.Collection a ([a] -> [a]) instance GHC.Classes.Ord a => BNFC.Utils.Singleton.Collection a (Data.Set.Internal.Set a) instance GHC.Classes.Ord k => BNFC.Utils.Singleton.Collection (k, a) (Data.Map.Internal.Map k a) instance BNFC.Utils.Singleton.Singleton a (GHC.Maybe.Maybe a) instance BNFC.Utils.Singleton.Singleton a [a] instance BNFC.Utils.Singleton.Singleton a ([a] -> [a]) instance BNFC.Utils.Singleton.Singleton a (GHC.Base.NonEmpty a) instance BNFC.Utils.Singleton.Singleton a (Data.Set.Internal.Set a) instance BNFC.Utils.Singleton.Singleton (k, a) (Data.Map.Internal.Map k a) -- | Extension to the 'Prelude'. module BNFC.Prelude -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. In other words, it evaluates the first -- argument a to weak head normal form (WHNF). seq is -- usually introduced to improve performance by avoiding unneeded -- laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> b -> b infixr 0 `seq` -- | <math>. filter, applied to a predicate and a list, -- returns the list of those elements that satisfy the predicate; i.e., -- --
-- filter p xs = [ x | x <- xs, p x] ---- --
-- >>> filter odd [1, 2, 3] -- [1,3] --filter :: (a -> Bool) -> [a] -> [a] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- --
-- zip [1, 2] ['a', 'b'] = [(1, 'a'), (2, 'b')] ---- -- If one input list is short, excess elements of the longer list are -- discarded: -- --
-- zip [1] ['a', 'b'] = [(1, 'a')] -- zip [1, 2] ['a'] = [(1, 'a')] ---- -- zip is right-lazy: -- --
-- zip [] _|_ = [] -- zip _|_ [] = _|_ ---- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zip :: [a] -> [b] -> [(a, b)] -- | The print function outputs a value of any printable type to the -- standard output device. Printable types are those that are instances -- of class Show; print converts values to strings for -- output using the show operation and adds a newline. -- -- For example, a program to print the first 20 integers and their powers -- of 2 could be written as: -- --
-- main = print ([(n, 2^n) | n <- [0..19]]) --print :: Show a => a -> IO () -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
-- f x | x < 0 = ... -- | otherwise = ... --otherwise :: Bool -- | <math>. map f xs is the list obtained by -- applying f to each element of xs, i.e., -- --
-- map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] -- map f [x1, x2, ...] == [f x1, f x2, ...] ---- --
-- >>> map (+1) [1, 2, 3] --map :: (a -> b) -> [a] -> [b] -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- -- Note that ($) is levity-polymorphic in its result -- type, so that foo $ True where foo :: Bool -> -- Int# is well-typed. ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $ -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | The Bounded class is used to name the upper and lower limits of -- a type. Ord is not a superclass of Bounded since types -- that are not totally ordered may also have upper and lower bounds. -- -- The Bounded class may be derived for any enumeration type; -- minBound is the first constructor listed in the data -- declaration and maxBound is the last. Bounded may also -- be derived for single-constructor datatypes whose constituent types -- are in Bounded. class Bounded a minBound :: Bounded a => a maxBound :: Bounded a => a -- | Class Enum defines operations on sequentially ordered types. -- -- The enumFrom... methods are used in Haskell's translation of -- arithmetic sequences. -- -- Instances of Enum may be derived for any enumeration type -- (types whose constructors have no fields). The nullary constructors -- are assumed to be numbered left-to-right by fromEnum from -- 0 through n-1. See Chapter 10 of the Haskell -- Report for more details. -- -- For any type that is an instance of class Bounded as well as -- Enum, the following should hold: -- --
-- enumFrom x = enumFromTo x maxBound -- enumFromThen x y = enumFromThenTo x y bound -- where -- bound | fromEnum y >= fromEnum x = maxBound -- | otherwise = minBound --class Enum a -- | the successor of a value. For numeric types, succ adds 1. succ :: Enum a => a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: Enum a => a -> a -- | Convert from an Int. toEnum :: Enum a => Int -> a -- | Convert to an Int. It is implementation-dependent what -- fromEnum returns when applied to a value that is too large to -- fit in an Int. fromEnum :: Enum a => a -> Int -- | Used in Haskell's translation of [n..] with [n..] = -- enumFrom n, a possible implementation being enumFrom n = n : -- enumFrom (succ n). For example: -- --
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: -- Int]
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: -- Int]
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo 4 2 -6 :: [Integer] = -- [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
-- (x `quot` y)*y + (x `rem` y) == x --rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
-- (x `div` y)*y + (x `mod` y) == x --mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer infixl 7 `mod` infixl 7 `div` infixl 7 `rem` infixl 7 `quot` -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Instances of Monad should satisfy the following: -- --
-- do a <- as -- bs a --(>>=) :: Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
-- do as -- bs --(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. class Functor (f :: Type -> Type) -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. fmap :: Functor f => (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | Basic numeric class. -- -- The Haskell Report defines no laws for Num. However, -- (+) and (*) are customarily expected -- to define a ring and have the following properties: -- --
-- abs x * signum x == x ---- -- For real numbers, the signum is either -1 (negative), -- 0 (zero) or 1 (positive). signum :: Num a => a -> a -- | Conversion from an Integer. An integer literal represents the -- application of the function fromInteger to the appropriate -- value of type Integer, so such literals have type -- (Num a) => a. fromInteger :: Num a => Integer -> a infixl 6 - infixl 6 + infixl 7 * -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- The Haskell Report defines no laws for Ord. However, -- <= is customarily expected to implement a non-strict partial -- order and have the following properties: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault ---- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
-- instance Read T where -- readPrec = ... -- readListPrec = readListPrecDefault --class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] class (Num a, Ord a) => Real a -- | the rational equivalent of its real argument with full precision toRational :: Real a => a -> Rational -- | Efficient, machine-independent access to the components of a -- floating-point number. class (RealFrac a, Floating a) => RealFloat a -- | a constant function, returning the radix of the representation (often -- 2) floatRadix :: RealFloat a => a -> Integer -- | a constant function, returning the number of digits of -- floatRadix in the significand floatDigits :: RealFloat a => a -> Int -- | a constant function, returning the lowest and highest values the -- exponent may assume floatRange :: RealFloat a => a -> (Int, Int) -- | The function decodeFloat applied to a real floating-point -- number returns the significand expressed as an Integer and an -- appropriately scaled exponent (an Int). If -- decodeFloat x yields (m,n), then x -- is equal in value to m*b^^n, where b is the -- floating-point radix, and furthermore, either m and -- n are both zero or else b^(d-1) <= abs m < -- b^d, where d is the value of floatDigits -- x. In particular, decodeFloat 0 = (0,0). If the -- type contains a negative zero, also decodeFloat (-0.0) = -- (0,0). The result of decodeFloat x is -- unspecified if either of isNaN x or -- isInfinite x is True. decodeFloat :: RealFloat a => a -> (Integer, Int) -- | encodeFloat performs the inverse of decodeFloat in the -- sense that for finite x with the exception of -0.0, -- uncurry encodeFloat (decodeFloat x) = x. -- encodeFloat m n is one of the two closest -- representable floating-point numbers to m*b^^n (or -- ±Infinity if overflow occurs); usually the closer, but if -- m contains too many bits, the result may be rounded in the -- wrong direction. encodeFloat :: RealFloat a => Integer -> Int -> a -- | exponent corresponds to the second component of -- decodeFloat. exponent 0 = 0 and for finite -- nonzero x, exponent x = snd (decodeFloat x) -- + floatDigits x. If x is a finite floating-point -- number, it is equal in value to significand x * b ^^ -- exponent x, where b is the floating-point radix. -- The behaviour is unspecified on infinite or NaN values. exponent :: RealFloat a => a -> Int -- | The first component of decodeFloat, scaled to lie in the open -- interval (-1,1), either 0.0 or of absolute -- value >= 1/b, where b is the floating-point -- radix. The behaviour is unspecified on infinite or NaN -- values. significand :: RealFloat a => a -> a -- | multiplies a floating-point number by an integer power of the radix scaleFloat :: RealFloat a => Int -> a -> a -- | True if the argument is an IEEE "not-a-number" (NaN) value isNaN :: RealFloat a => a -> Bool -- | True if the argument is an IEEE infinity or negative infinity isInfinite :: RealFloat a => a -> Bool -- | True if the argument is too small to be represented in -- normalized format isDenormalized :: RealFloat a => a -> Bool -- | True if the argument is an IEEE negative zero isNegativeZero :: RealFloat a => a -> Bool -- | True if the argument is an IEEE floating point number isIEEE :: RealFloat a => a -> Bool -- | a version of arctangent taking two real floating-point arguments. For -- real floating x and y, atan2 y x -- computes the angle (from the positive x-axis) of the vector from the -- origin to the point (x,y). atan2 y x returns -- a value in the range [-pi, pi]. It follows the -- Common Lisp semantics for the origin when signed zeroes are supported. -- atan2 y 1, with y in a type that is -- RealFloat, should return the same value as atan -- y. A default definition of atan2 is provided, but -- implementors can provide a more accurate implementation. atan2 :: RealFloat a => a -> a -> a -- | Extracting components of fractions. class (Real a, Fractional a) => RealFrac a -- | The function properFraction takes a real fractional number -- x and returns a pair (n,f) such that x = -- n+f, and: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Show is equivalent to -- --
-- instance (Show a) => Show (Tree a) where -- -- showsPrec d (Leaf m) = showParen (d > app_prec) $ -- showString "Leaf " . showsPrec (app_prec+1) m -- where app_prec = 10 -- -- showsPrec d (u :^: v) = showParen (d > up_prec) $ -- showsPrec (up_prec+1) u . -- showString " :^: " . -- showsPrec (up_prec+1) v -- where up_prec = 5 ---- -- Note that right-associativity of :^: is ignored. For example, -- --
-- showsPrec d x r ++ s == showsPrec d x (r ++ s) ---- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | When a value is bound in do-notation, the pattern on the left -- hand side of <- might not match. In this case, this class -- provides a function to recover. -- -- A Monad without a MonadFail instance may only be used in -- conjunction with pattern that always match, such as newtypes, tuples, -- data types with only a single data constructor, and irrefutable -- patterns (~pat). -- -- Instances of MonadFail should satisfy the following law: -- fail s should be a left zero for >>=, -- --
-- fail s >>= f = fail s ---- -- If your Monad is also MonadPlus, a popular definition is -- --
-- fail _ = mzero --class Monad m => MonadFail (m :: Type -> Type) fail :: MonadFail m => String -> m a -- | A functor with application, providing operations to -- --
-- (<*>) = liftA2 id ---- --
-- liftA2 f x y = f <$> x <*> y ---- -- Further, any definition must satisfy the following: -- --
pure id <*> v = -- v
pure (.) <*> u -- <*> v <*> w = u <*> (v -- <*> w)
pure f <*> -- pure x = pure (f x)
u <*> pure y = -- pure ($ y) <*> u
-- forall x y. p (q x y) = f x . g y ---- -- it follows from the above that -- --
-- liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v ---- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative (f :: Type -> Type) -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. -- -- Using ApplicativeDo: 'fs <*> as' can be -- understood as the do expression -- --
-- do f <- fs -- a <- as -- pure (f a) --(<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. -- -- 'as *> bs' can be understood as the do -- expression -- --
-- do as -- bs ---- -- This is a tad complicated for our ApplicativeDo extension -- which will give it a Monad constraint. For an -- Applicative constraint we write it of the form -- --
-- do _ <- as -- b <- bs -- pure b --(*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. -- -- Using ApplicativeDo: 'as <* bs' can be -- understood as the do expression -- --
-- do a <- as -- bs -- pure a --(<*) :: Applicative f => f a -> f b -> f a infixl 4 <* infixl 4 *> infixl 4 <*> -- | Data structures that can be folded. -- -- For example, given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Foldable Tree where -- foldMap f Empty = mempty -- foldMap f (Leaf x) = f x -- foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r ---- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
-- instance Foldable Tree where -- foldr f z Empty = z -- foldr f z (Leaf x) = f x z -- foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l ---- -- Foldable instances are expected to satisfy the following -- laws: -- --
-- foldr f z t = appEndo (foldMap (Endo . f) t ) z ---- --
-- foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z ---- --
-- fold = foldMap id ---- --
-- length = getSum . foldMap (Sum . const 1) ---- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
-- sum = getSum . foldMap Sum ---- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
-- foldMap f = fold . fmap f ---- -- which implies that -- --
-- foldMap f . fmap g = foldMap (f . g) --class Foldable (t :: Type -> Type) -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) ---- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldr f z = foldr f z . toList --foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z `f` x1 -- in the above example) before applying them to the operator (e.g. to -- (`f` x2)). This results in a thunk chain <math> -- elements long, which then must be evaluated from the outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl f z = foldl f z . toList --foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
-- foldr1 f = foldr1 f . toList --foldr1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
-- foldl1 f = foldl1 f . toList --foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t a -> Int -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: (Foldable t, Ord a) => t a -> a -- | The sum function computes the sum of the numbers of a -- structure. sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. product :: (Foldable t, Num a) => t a -> a infix 4 `elem` -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- --
-- t :: (Applicative f, Applicative g) => f a -> g a ---- -- preserving the Applicative operations, i.e. -- --
-- t (pure x) = pure x -- t (f <*> x) = t f <*> t x ---- -- and the identity functor Identity and composition functors -- Compose are from Data.Functor.Identity and -- Data.Functor.Compose. -- -- A result of the naturality law is a purity law for traverse -- --
-- traverse pure = pure ---- -- (The naturality law is implied by parametricity and thus so is the -- purity law [1, p15].) -- -- Instances are similar to Functor, e.g. given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Traversable Tree where -- traverse f Empty = pure Empty -- traverse f (Leaf x) = Leaf <$> f x -- traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r ---- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- --
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- --
-- >>> "Hello world" <> mempty -- "Hello world" --mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. -- -- For most types, the default definition for mconcat will be -- used, but the function is included in the class definition so that an -- optimized version can be provided for specific types. -- --
-- >>> mconcat ["Hello", " ", "Haskell", "!"] -- "Hello Haskell!" --mconcat :: Monoid a => [a] -> a data Bool False :: Bool True :: Bool -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int -- | Arbitrary precision integers. In contrast with fixed-size integral -- types such as Int, the Integer type represents the -- entire infinite range of integers. -- -- For more information about this type's representation, see the -- comments in its implementation. data Integer -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a Nothing :: Maybe a Just :: a -> Maybe a data Ordering LT :: Ordering EQ :: Ordering GT :: Ordering -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a -- | A Word is an unsigned integral type, with the same size as -- Int. data Word -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). -- --
-- >>> let s = Left "foo" :: Either String Int -- -- >>> s -- Left "foo" -- -- >>> let n = Right 3 :: Either String Int -- -- >>> n -- Right 3 -- -- >>> :type s -- s :: Either String Int -- -- >>> :type n -- n :: Either String Int ---- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
-- >>> let s = Left "foo" :: Either String Int -- -- >>> let n = Right 3 :: Either String Int -- -- >>> fmap (*2) s -- Left "foo" -- -- >>> fmap (*2) n -- Right 6 ---- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
-- >>> import Data.Char ( digitToInt, isDigit ) -- -- >>> :{ -- let parseEither :: Char -> Either String Int -- parseEither c -- | isDigit c = Right (digitToInt c) -- | otherwise = Left "parse error" -- -- >>> :} ---- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
-- >>> :{ -- let parseMultiple :: Either String Int -- parseMultiple = do -- x <- parseEither '1' -- y <- parseEither '2' -- return (x + y) -- -- >>> :} ---- --
-- >>> parseMultiple -- Right 3 ---- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
-- >>> :{ -- let parseMultiple :: Either String Int -- parseMultiple = do -- x <- parseEither 'm' -- y <- parseEither '2' -- return (x + y) -- -- >>> :} ---- --
-- >>> parseMultiple -- Left "parse error" --data Either a b Left :: a -> Either a b Right :: b -> Either a b -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a -- | The computation appendFile file str function appends -- the string str, to the file file. -- -- Note that writeFile and appendFile write a literal -- string to a file. To write a value of any printable type, as with -- print, use the show function to convert the value to a -- string first. -- --
-- main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]]) --appendFile :: FilePath -> String -> IO () -- | The computation writeFile file str function writes the -- string str, to the file file. writeFile :: FilePath -> String -> IO () -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | The interact function takes a function of type -- String->String as its argument. The entire input from the -- standard input device is passed to this function as its argument, and -- the resulting string is output on the standard output device. interact :: (String -> String) -> IO () -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | The same as putStr, but adds a newline character. putStrLn :: String -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | Write a character to the standard output device (same as -- hPutChar stdout). putChar :: Char -> IO () -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | File and directory names are values of type String, whose -- precise meaning is operating system dependent. Files can be opened, -- yielding a handle which can then be used to operate on the contents of -- that file. type FilePath = String -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
-- instance Monad IO where -- ... -- fail s = ioError (userError s) --userError :: String -> IOError -- | The Haskell 2010 type for exceptions in the IO monad. Any I/O -- operation may raise an IOError instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see Exception. -- -- In Haskell 2010, this is an opaque type. type IOError = IOException -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | Determines whether all elements of the structure satisfy the -- predicate. all :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. any :: Foldable t => (a -> Bool) -> t a -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. or :: Foldable t => t Bool -> Bool -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | Map a function over all the elements of a container and concatenate -- the resulting lists. concatMap :: Foldable t => (a -> [b]) -> t a -> [b] -- | The concatenation of all the elements of a container of lists. concat :: Foldable t => t [a] -> [a] -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
-- >>> unwords ["Lorem", "ipsum", "dolor"] -- "Lorem ipsum dolor" --unwords :: [String] -> String -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
-- >>> words "Lorem ipsum\ndolor" -- ["Lorem","ipsum","dolor"] --words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
-- >>> unlines ["Hello", "World", "!"] -- "Hello\nWorld\n!\n" --unlines :: [String] -> String -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
-- >>> lines "" -- [] ---- --
-- >>> lines "\n" -- [""] ---- --
-- >>> lines "one" -- ["one"] ---- --
-- >>> lines "one\n" -- ["one"] ---- --
-- >>> lines "one\n\n" -- ["one",""] ---- --
-- >>> lines "one\ntwo" -- ["one","two"] ---- --
-- >>> lines "one\ntwo\n" -- ["one","two"] ---- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | The read function reads input from a string, which must be -- completely consumed by the input process. read fails with an -- error if the parse is unsuccessful, and it is therefore -- discouraged from being used in real applications. Use readMaybe -- or readEither for safe alternatives. -- --
-- >>> read "123" :: Int -- 123 ---- --
-- >>> read "hello" :: Int -- *** Exception: Prelude.read: no parse --read :: Read a => String -> a -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. -- --
-- >>> let s = Left "foo" :: Either String Int -- -- >>> let n = Right 3 :: Either String Int -- -- >>> either length (*2) s -- 3 -- -- >>> either length (*2) n -- 6 --either :: (a -> c) -> (b -> c) -> Either a b -> c -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- --
-- >>> zipWith (+) [1, 2, 3] [4, 5, 6] -- [5,7,9] ---- -- zipWith is right-lazy: -- --
-- zipWith f [] _|_ = [] ---- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: [a] -> Int -> a infixl 9 !! -- | <math>. lookup key assocs looks up a key in an -- association list. -- --
-- >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")] -- Just "second" --lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) -- break (< 9) [1,2,3] == ([],[1,2,3]) -- break (> 9) [1,2,3] == ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) -- span (< 9) [1,2,3] == ([1,2,3],[]) -- span (< 0) [1,2,3] == ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- splitAt 6 "Hello World!" == ("Hello ","World!") -- splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) -- splitAt 1 [1,2,3] == ([1],[2,3]) -- splitAt 3 [1,2,3] == ([1,2,3],[]) -- splitAt 4 [1,2,3] == ([1,2,3],[]) -- splitAt 0 [1,2,3] == ([],[1,2,3]) -- splitAt (-1) [1,2,3] == ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs: -- --
-- drop 6 "Hello World!" == "World!" -- drop 3 [1,2,3,4,5] == [4,5] -- drop 3 [1,2] == [] -- drop 3 [] == [] -- drop (-1) [1,2] == [1,2] -- drop 0 [1,2] == [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs: -- --
-- take 5 "Hello World!" == "Hello" -- take 3 [1,2,3,4,5] == [1,2,3] -- take 3 [1,2] == [1,2] -- take 3 [] == [] -- take (-1) [1,2] == [] -- take 0 [1,2] == [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs: -- --
-- dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3] -- dropWhile (< 9) [1,2,3] == [] -- dropWhile (< 0) [1,2,3] == [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p: -- --
-- takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] -- takeWhile (< 9) [1,2,3] == [1,2,3] -- takeWhile (< 0) [1,2,3] == [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | cycle ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity on -- infinite lists. cycle :: [a] -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: Int -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: a -> [a] -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] ---- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See -- iterate' for a strict variant of this function. iterate :: (a -> a) -> a -> [a] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. scanr1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. scanr is the right-to-left dual of scanl. -- Note that -- --
-- head (scanr f z xs) == foldr f z xs. --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanl1 is a variant of scanl that has no -- starting value argument: -- --
-- scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] --scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. scanl is similar to foldl, but returns a -- list of successive reduced values from the left: -- --
-- scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. init :: [a] -> [a] -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. last :: [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. tail :: [a] -> [a] -- | <math>. Extract the first element of a list, which must be -- non-empty. head :: [a] -> a -- | The maybe function takes a default value, a function, and a -- Maybe value. If the Maybe value is Nothing, the -- function returns the default value. Otherwise, it applies the function -- to the value inside the Just and returns the result. -- --
-- >>> maybe False odd (Just 3) -- True ---- --
-- >>> maybe False odd Nothing -- False ---- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
-- >>> import Text.Read ( readMaybe ) -- -- >>> maybe 0 (*2) (readMaybe "5") -- 10 -- -- >>> maybe 0 (*2) (readMaybe "") -- 0 ---- -- Apply show to a Maybe Int. If we have Just n, -- we want to show the underlying Int n. But if we have -- Nothing, we return the empty string instead of (for example) -- "Nothing": -- --
-- >>> maybe "" show (Just 5) -- "5" -- -- >>> maybe "" show Nothing -- "" --maybe :: b -> (a -> b) -> Maybe a -> b -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
-- ($) :: (a -> b) -> a -> b -- (<$>) :: Functor f => (a -> b) -> f a -> f b ---- -- Whereas $ is function application, <$> is function -- application lifted over a Functor. -- --
-- >>> show <$> Nothing -- Nothing -- -- >>> show <$> Just 3 -- Just "3" ---- -- Convert from an Either Int Int to an -- Either Int String using show: -- --
-- >>> show <$> Left 17 -- Left 17 -- -- >>> show <$> Right 17 -- Right "17" ---- -- Double each element of a list: -- --
-- >>> (*2) <$> [1,2,3] -- [2,4,6] ---- -- Apply even to the second element of a pair: -- --
-- >>> even <$> (2,2) -- (2,True) --(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | uncurry converts a curried function to a function on pairs. -- --
-- >>> uncurry (+) (1,2) -- 3 ---- --
-- >>> uncurry ($) (show, 1) -- "1" ---- --
-- >>> map (uncurry max) [(1,2), (3,4), (6,8)] -- [2,4,8] --uncurry :: (a -> b -> c) -> (a, b) -> c -- | curry converts an uncurried function to a curried function. -- --
-- >>> curry fst 1 2 -- 1 --curry :: ((a, b) -> c) -> a -> b -> c -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: a -> a -> a -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | Strict (call-by-value) application operator. It takes a function and -- an argument, evaluates the argument to weak head normal form (WHNF), -- then calls the function with that value. ($!) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $! -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
-- >>> flip (++) "hello" "world" -- "worldhello" --flip :: (a -> b -> c) -> b -> a -> c -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | const x is a unary function which evaluates to x for -- all inputs. -- --
-- >>> const 42 "hello" -- 42 ---- --
-- >>> map (const 42) [0..3] -- [42,42,42,42] --const :: a -> b -> a -- | Identity function. -- --
-- id x = x --id :: a -> a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | A String is a list of characters. String constants in Haskell -- are values of type String. -- -- See Data.List for operations on lists. type String = [Char] -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a -- | error stops execution and displays an error message. error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a -- | Boolean "and", lazy in the second argument (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or", lazy in the second argument (||) :: Bool -> Bool -> Bool infixr 2 || -- | Boolean "not" not :: Bool -> Bool -- | Prepend an element to the stream. (<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 <| -- | nonEmpty efficiently turns a normal list into a NonEmpty -- stream, producing Nothing if the input is empty. nonEmpty :: [a] -> Maybe (NonEmpty a) pattern (:|) :: () => a -> [a] -> NonEmpty a infixr 5 :| -- | Non-empty String. type String1 = List1 Char -- | Non-empty list. TODO change to newtype? type List1 = NonEmpty trim1 :: String -> Maybe String1 -- | Lists of length ≥2. data List2 a List2 :: a -> a -> [a] -> List2 a -- | A monad transformer that adds exceptions to other monads. -- -- ExceptT constructs a monad parameterized over two things: -- --
-- do { action1; action2; action3 } `catchError` handler ---- -- where the action functions can call throwError. Note -- that handler and the do-block must have the same return type. catchError :: MonadError e m => m a -> (e -> m a) -> m a -- | The inverse of ExceptT. runExceptT :: ExceptT e m a -> m (Either e a) -- | Retrieves a function of the current environment. asks :: MonadReader r m => (r -> a) -> m a -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r (m :: Type -> Type) | m -> r -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Executes a computation in a modified environment. local :: MonadReader r m => (r -> r) -> m a -> m a -- | Retrieves a function of the current environment. reader :: MonadReader r m => (r -> a) -> m a -- | The reader monad transformer, which adds a read-only environment to -- the given monad. -- -- The return function ignores the environment, while -- >>= passes the inherited environment to both -- subcomputations. newtype ReaderT r (m :: Type -> Type) a ReaderT :: (r -> m a) -> ReaderT r (m :: Type -> Type) a [runReaderT] :: ReaderT r (m :: Type -> Type) a -> r -> m a -- | Transform the computation inside a ReaderT. -- --
runReaderT (mapReaderT f m) = f . -- runReaderT m
-- Main> :t modify ((+1) :: Int -> Int) -- modify (...) :: (MonadState Int a) => a () ---- -- This says that modify (+1) acts over any Monad that is a -- member of the MonadState class, with an Int state. modify :: MonadState s m => (s -> s) -> m () -- | Gets specific component of the state, using a projection function -- supplied. gets :: MonadState s m => (s -> a) -> m a -- | Minimal definition is either both of get and put or -- just state class Monad m => MonadState s (m :: Type -> Type) | m -> s -- | Return the state from the internals of the monad. get :: MonadState s m => m s -- | Replace the state inside the monad. put :: MonadState s m => s -> m () -- | Embed a simple state action into the monad. state :: MonadState s m => (s -> (a, s)) -> m a -- | A state transformer monad parameterized by: -- --
evalStateT m s = liftM fst -- (runStateT m s)
execStateT m s = liftM snd -- (runStateT m s)
-- runReaderT :: ReaderT r m a -> r -> m a -- StT (ReaderT r) a ~ a -- -- runStateT :: StateT s m a -> s -> m (a, s) -- StT (StateT s) a ~ (a, s) -- -- runMaybeT :: MaybeT m a -> m (Maybe a) -- StT MaybeT a ~ Maybe a ---- -- Provided type instances: -- --
-- StT IdentityT a ~ a -- StT MaybeT a ~ Maybe a -- StT (ErrorT e) a ~ Error e => Either e a -- StT (ExceptT e) a ~ Either e a -- StT ListT a ~ [a] -- StT (ReaderT r) a ~ a -- StT (StateT s) a ~ (a, s) -- StT (WriterT w) a ~ Monoid w => (a, w) -- StT (RWST r w s) a ~ Monoid w => (a, s, w) --type family StT (t :: Type -> Type -> Type -> Type) a -- | The MonadTransControl type class is a stronger version of -- MonadTrans: -- -- Instances of MonadTrans know how to -- lift actions in the base monad to the transformed -- monad. These lifted actions, however, are completely unaware of the -- monadic state added by the transformer. -- -- MonadTransControl instances are aware of the monadic -- state of the transformer and allow to save and restore this state. -- -- This allows to lift functions that have a monad transformer in both -- positive and negative position. Take, for example, the function -- --
-- withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r ---- -- MonadTrans instances can only lift the return type of -- the withFile function: -- --
-- withFileLifted :: MonadTrans t => FilePath -> IOMode -> (Handle -> IO r) -> t IO r -- withFileLifted file mode action = lift (withFile file mode action) ---- -- However, MonadTrans is not powerful enough to make -- withFileLifted accept a function that returns t IO. -- The reason is that we need to take away the transformer layer in order -- to pass the function to withFile. -- MonadTransControl allows us to do this: -- --
-- withFileLifted' :: (Monad (t IO), MonadTransControl t) => FilePath -> IOMode -> (Handle -> t IO r) -> t IO r -- withFileLifted' file mode action = liftWith (\run -> withFile file mode (run . action)) >>= restoreT . return --class MonadTrans t => MonadTransControl (t :: Type -> Type -> Type -> Type) where { -- | Monadic state of t. -- -- The monadic state of a monad transformer is the result type of its -- run function, e.g.: -- --
-- runReaderT :: ReaderT r m a -> r -> m a -- StT (ReaderT r) a ~ a -- -- runStateT :: StateT s m a -> s -> m (a, s) -- StT (StateT s) a ~ (a, s) -- -- runMaybeT :: MaybeT m a -> m (Maybe a) -- StT MaybeT a ~ Maybe a ---- -- Provided type instances: -- --
-- StT IdentityT a ~ a -- StT MaybeT a ~ Maybe a -- StT (ErrorT e) a ~ Error e => Either e a -- StT (ExceptT e) a ~ Either e a -- StT ListT a ~ [a] -- StT (ReaderT r) a ~ a -- StT (StateT s) a ~ (a, s) -- StT (WriterT w) a ~ Monoid w => (a, w) -- StT (RWST r w s) a ~ Monoid w => (a, s, w) --type family StT (t :: Type -> Type -> Type -> Type) a; } -- | liftWith is similar to lift in that it lifts a -- computation from the argument monad to the constructed monad. -- -- Instances should satisfy similar laws as the MonadTrans laws: -- --
-- liftWith (\_ -> return a) = return a ---- --
-- liftWith (\_ -> m >>= f) = liftWith (\_ -> m) >>= (\a -> liftWith (\_ -> f a)) ---- -- The difference with lift is that before lifting the -- m computation liftWith captures the state of -- t. It then provides the m computation with a -- Run function that allows running t n computations in -- n (for all n) on the captured state, e.g. -- --
-- withFileLifted :: (Monad (t IO), MonadTransControl t) => FilePath -> IOMode -> (Handle -> t IO r) -> t IO r -- withFileLifted file mode action = liftWith (\run -> withFile file mode (run . action)) >>= restoreT . return ---- -- If the Run function is ignored, liftWith coincides -- with lift: -- --
-- lift f = liftWith (\_ -> f) ---- -- Implementations use the Run function associated with a -- transformer: -- --
-- liftWith :: Monad m => ((Monad n => ReaderT r n b -> n b) -> m a) -> ReaderT r m a -- liftWith f = ReaderT (\r -> f (\action -> runReaderT action r)) -- -- liftWith :: Monad m => ((Monad n => StateT s n b -> n (b, s)) -> m a) -> StateT s m a -- liftWith f = StateT (\s -> liftM (\x -> (x, s)) (f (\action -> runStateT action s))) -- -- liftWith :: Monad m => ((Monad n => MaybeT n b -> n (Maybe b)) -> m a) -> MaybeT m a -- liftWith f = MaybeT (liftM Just (f runMaybeT)) --liftWith :: (MonadTransControl t, Monad m) => (Run t -> m a) -> t m a -- | Construct a t computation from the monadic state of -- t that is returned from a Run function. -- -- Instances should satisfy: -- --
-- liftWith (\run -> run t) >>= restoreT . return = t ---- -- restoreT is usually implemented through the constructor of -- the monad transformer: -- --
-- ReaderT :: (r -> m a) -> ReaderT r m a -- restoreT :: m a -> ReaderT r m a -- restoreT action = ReaderT { runReaderT = const action } -- -- StateT :: (s -> m (a, s)) -> StateT s m a -- restoreT :: m (a, s) -> StateT s m a -- restoreT action = StateT { runStateT = const action } -- -- MaybeT :: m (Maybe a) -> MaybeT m a -- restoreT :: m (Maybe a) -> MaybeT m a -- restoreT action = MaybeT action ---- -- Example type signatures: -- --
-- restoreT :: Monad m => m a -> IdentityT m a -- restoreT :: Monad m => m (Maybe a) -> MaybeT m a -- restoreT :: (Monad m, Error e) => m (Either e a) -> ErrorT e m a -- restoreT :: Monad m => m (Either e a) -> ExceptT e m a -- restoreT :: Monad m => m [a] -> ListT m a -- restoreT :: Monad m => m a -> ReaderT r m a -- restoreT :: Monad m => m (a, s) -> StateT s m a -- restoreT :: (Monad m, Monoid w) => m (a, w) -> WriterT w m a -- restoreT :: (Monad m, Monoid w) => m (a, s, w) -> RWST r w s m a --restoreT :: (MonadTransControl t, Monad m) => m (StT t a) -> t m a -- | A writer monad parameterized by: -- --
-- nubIntOn fromEnum xs --nubOrd :: Ord a => [a] -> [a] -- | List of elements of a structure, from left to right. toList :: Foldable t => t a -> [a] -- | Determines whether all elements of the structure satisfy the -- predicate. all :: Foldable t => (a -> Bool) -> t a -> Bool -- | on b u x y runs the binary function b -- on the results of applying unary function u to two -- arguments x and y. From the opposite perspective, it -- transforms two inputs and combines the outputs. -- --
-- ((+) `on` f) x y = f x + f y ---- -- Typical usage: sortBy (compare `on` -- fst). -- -- Algebraic properties: -- --
(*) `on` id = (*) -- (if (*) ∉ {⊥, const -- ⊥})
((*) `on` f) `on` g = (*) `on` (f . g)
flip on f . flip on g = flip on (g . -- f)
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --
-- >>> import Data.List.NonEmpty -- -- >>> sconcat $ "Hello" :| [" ", "Haskell", "!"] -- "Hello Haskell!" --sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --
-- >>> stimes 4 [1] -- [1,1,1,1] --stimes :: (Semigroup a, Integral b) => b -> a -> a infixr 6 <> -- | Prepend an element to the stream. (<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 <| -- | nonEmpty efficiently turns a normal list into a NonEmpty -- stream, producing Nothing if the input is empty. nonEmpty :: [a] -> Maybe (NonEmpty a) pattern (:|) :: () => a -> [a] -> NonEmpty a infixr 5 :| -- | A Map from keys k to values a. -- -- The Semigroup operation for Map is union, which -- prefers values from the left operand. If m1 maps a key -- k to a value a1, and m2 maps the same key -- to a different value a2, then their union m1 <> -- m2 maps k to a1. data Map k a -- | A set of values a. data Set 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]) forMM_ :: (Monad m, Foldable t) => m (t a) -> (a -> m ()) -> m () -- | Tools to manipulate regular expressions. module BNFC.Types.Regex -- | Regular expressions are constructed over character classes. -- -- Use smart constructors to ensure invariants. data Regex -- | Atomic regular expression. RChar :: CharClass -> Regex -- | Alternative/sum: List free of duplicates and RAlt. We use -- list instead of set to preserve the order given by the user. Empty -- list would mean empty language, but this is instead represented by the -- empty character class. RAlts :: List2 Regex -> Regex -- | Difference. Most lexer generators do not support difference in -- general, only at the level of character classes. LBNF has general -- difference, so it is represented here. RMinus :: Regex -> Regex -> Regex -- | Language of the empty word (empty sequence). REps :: Regex -- | Sequence/product. List free of RSeq. Empty list is -- eps (language of the empty word). RSeqs :: List2 Regex -> Regex -- | 0 or more repetitions. Regex isn't RStar, RPlus, -- ROpt, RAlts [] nor REps. RStar :: Regex -> Regex -- | 1 or more repetitions. Regex isn't RStar, RPlus, -- ROpt, RAlts [] nor REps. RPlus :: Regex -> Regex -- | 0 or 1 repetitions. Regex isn't RStar, RPlus, -- ROpt, RAlts [] nor REps. ROpt :: Regex -> Regex pattern REmpty :: Regex pattern RAlt :: Regex -> Regex -> Regex pattern RSeq :: Regex -> Regex -> Regex -- | Check if a regular expression is nullable (accepts the empty string). nullable :: Regex -> Bool -- | Check if a regular expression matches at least one word. -- -- For differences, this check may err on the positive side. class Satisfiable a satisfiable :: Satisfiable a => a -> Bool -- | Character classes are regular expressions that recognize character -- sequences of length exactly one. These are often distinguished from -- arbitrary regular expressions in lexer generators, e.g. in -- alex. -- -- We represent character classes as a difference of unions of atomic -- character classes. -- -- Semantics: ⟦ CMinus ccYes ccNo ⟧ = ⟦ ccYes ⟧ ⟦ ccNo ⟧ data CharClass CMinus :: CharClassUnion -> CharClassUnion -> CharClass -- | Character in question must be in one of these character classes. [ccYes] :: CharClass -> CharClassUnion -- | Character in question must not be in one of these character classes. -- Must be empty if ccYes is empty. [ccNo] :: CharClass -> CharClassUnion pattern CEmpty :: CharClass pattern CC :: CharClassUnion -> CharClass -- | Possibly overlapping union of character classes. data CharClassUnion -- | Any character, LBNF char. CAny :: CharClassUnion -- | Any of the given (≥0) alternatives. List is free of duplicates. CAlt :: [CharClassAtom] -> CharClassUnion pattern CCEmpty :: CharClassUnion -- | Atomic character class. data CharClassAtom -- | A single character. CChar :: Char -> CharClassAtom -- | 0-9, LBNF digit. CDigit :: CharClassAtom -- | Lower case character, LBNF lower. CLower :: CharClassAtom -- | Upper case character, LBNF upper. CUpper :: CharClassAtom rChar :: Char -> Regex -- | Simplifications included, but no distributivity. rSeq :: Regex -> Regex -> Regex rSeqs :: [Regex] -> Regex rAlt :: Regex -> Regex -> Regex rAlts :: [Regex] -> Regex rMinus :: Regex -> Regex -> Regex rStar :: Regex -> Regex rPlus :: Regex -> Regex rOpt :: Regex -> Regex -- | Disjunction of two character classes is either a character class again -- (RChar) or simply the disjunction (RAlt). -- -- (p1 m1) ∪ (p2 m2) = (p1 ∪ p2) (m1 ∪ m2) if p1 ⊥ m2 -- and p2 ⊥ m1 cAlt :: CharClass -> CharClass -> Regex -- | Disjunction of two character classes is either a character class again -- (RChar) or simply the disjunction (RMinus). -- -- (p1 m1) (0 m2) = p1 m1 (p1 m1) (p2 m2) = p1 (m1 ∪ -- p2) if p1 m2 = p1 cMinus :: CharClass -> CharClass -> Regex -- | Match given characters. cChar :: Char -> CharClass -- | Match any of the given characters. cAlts :: [Char] -> CharClass cDigit :: CharClass cLower :: CharClass cUpper :: CharClass cLetter :: CharClass cAny :: CharClass cAtom :: CharClassAtom -> CharClass -- | Smart constructor for CharClass from difference.. -- -- Mutually reduce: (A - B) = (A B) - (B A) ccuMinus :: CharClassUnion -> CharClassUnion -> Either CharClass CharClassUnion onlyOneChar :: CharClassUnion -> Bool isEmpty :: CharClassUnion -> Bool instance GHC.Show.Show BNFC.Types.Regex.CharClassAtom instance GHC.Classes.Ord BNFC.Types.Regex.CharClassAtom instance GHC.Classes.Eq BNFC.Types.Regex.CharClassAtom instance GHC.Show.Show BNFC.Types.Regex.CharClassUnion instance GHC.Classes.Ord BNFC.Types.Regex.CharClassUnion instance GHC.Show.Show BNFC.Types.Regex.CharClass instance GHC.Classes.Ord BNFC.Types.Regex.CharClass instance GHC.Classes.Eq BNFC.Types.Regex.CharClass instance GHC.Show.Show BNFC.Types.Regex.Regex instance GHC.Classes.Ord BNFC.Types.Regex.Regex instance GHC.Classes.Eq BNFC.Types.Regex.Regex instance BNFC.Types.Regex.Satisfiable BNFC.Types.Regex.Regex instance BNFC.Types.Regex.Satisfiable BNFC.Types.Regex.CharClass instance BNFC.Types.Regex.Satisfiable BNFC.Types.Regex.CharClassUnion instance GHC.Classes.Eq BNFC.Types.Regex.CharClassUnion instance GHC.Base.Semigroup BNFC.Types.Regex.CharClassUnion instance GHC.Base.Monoid BNFC.Types.Regex.CharClassUnion module BNFC.Types.Position data WithPosition a WithPosition :: !Position -> a -> WithPosition a [wpPos] :: WithPosition a -> !Position [wpThing] :: WithPosition a -> a data WithPosition' a WithPosition' :: !Position' -> a -> WithPosition' a [wpPos'] :: WithPosition' a -> !Position' [wpThing'] :: WithPosition' a -> a type Position' = Maybe Position data Position Position :: !Int -> !Int -> Position -- | Starting at line, counting from 1. (0 for invalid line.) [posLine] :: Position -> !Int -- | Starting at column, counting from 1. (0 for invalid column.) [posCol] :: Position -> !Int -- | Something that can be parsed into a Position. class ToPosition p toPosition :: ToPosition p => p -> Position -- | Something that can be parsed into a Position'. class ToPosition' p toPosition' :: ToPosition' p => p -> Position' instance GHC.Show.Show BNFC.Types.Position.Position instance GHC.Classes.Ord BNFC.Types.Position.Position instance GHC.Classes.Eq BNFC.Types.Position.Position instance Data.Traversable.Traversable BNFC.Types.Position.WithPosition' instance Data.Foldable.Foldable BNFC.Types.Position.WithPosition' instance GHC.Base.Functor BNFC.Types.Position.WithPosition' instance GHC.Show.Show a => GHC.Show.Show (BNFC.Types.Position.WithPosition' a) instance Data.Traversable.Traversable BNFC.Types.Position.WithPosition instance Data.Foldable.Foldable BNFC.Types.Position.WithPosition instance GHC.Base.Functor BNFC.Types.Position.WithPosition instance GHC.Show.Show a => GHC.Show.Show (BNFC.Types.Position.WithPosition a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.Types.Position.WithPosition a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.Types.Position.WithPosition a) instance BNFC.Types.Position.ToPosition' BNFC.Types.Position.Position' instance BNFC.Types.Position.ToPosition' BNFC.Types.Position.Position instance BNFC.Types.Position.ToPosition' (GHC.Types.Int, GHC.Types.Int) instance BNFC.Types.Position.ToPosition' (GHC.Maybe.Maybe (GHC.Types.Int, GHC.Types.Int)) instance BNFC.Types.Position.ToPosition BNFC.Types.Position.Position instance BNFC.Types.Position.ToPosition (GHC.Types.Int, GHC.Types.Int) instance BNFC.Utils.Decoration.Decoration BNFC.Types.Position.WithPosition instance BNFC.Utils.Decoration.Decoration BNFC.Types.Position.WithPosition' instance GHC.Enum.Bounded BNFC.Types.Position.Position module BNFC.Options.Target -- | Target languages data TargetLanguage TargetAgda :: TargetLanguage TargetC :: TargetLanguage TargetCpp :: TargetLanguage TargetCppNoStl :: TargetLanguage TargetHaskell :: TargetLanguage TargetLatex :: TargetLanguage TargetJava :: TargetLanguage TargetOCaml :: TargetLanguage TargetPygments :: TargetLanguage TargetTxt2Tags :: TargetLanguage TargetCheck :: TargetLanguage instance GHC.Classes.Ord BNFC.Options.Target.TargetLanguage instance GHC.Enum.Enum BNFC.Options.Target.TargetLanguage instance GHC.Enum.Bounded BNFC.Options.Target.TargetLanguage instance GHC.Classes.Eq BNFC.Options.Target.TargetLanguage instance GHC.Show.Show BNFC.Options.Target.TargetLanguage -- | Global options parser. module BNFC.Options.GlobalOptions -- | Global options. data GlobalOptions GlobalOptions :: Bool -> Bool -> Bool -> Maybe FilePath -> Bool -> FilePath -> GlobalOptions [optVerbose] :: GlobalOptions -> Bool [optDryRun] :: GlobalOptions -> Bool [optForce] :: GlobalOptions -> Bool [optOutDir] :: GlobalOptions -> Maybe FilePath [optMakeFile] :: GlobalOptions -> Bool [optInput] :: GlobalOptions -> FilePath -- | Global options parser. globalOptionsParser :: Parser GlobalOptions instance GHC.Show.Show BNFC.Options.GlobalOptions.GlobalOptions module BNFC.Backend.Latex.State newtype LatexBackendState LatexSt :: GlobalOptions -> LatexBackendState [globalOpt] :: LatexBackendState -> GlobalOptions module BNFC.Lexing -- | Create regex for multiline comments. -- --
-- >>> debugPrint $ mkRegMultilineComment "<" ">" -- '<'(char-'>')*'>' ---- --
-- >>> debugPrint $ mkRegMultilineComment "/*" "*/" -- {"/*"}(char-'*')*'*'((char-["*/"])(char-'*')*'*'|'*')*'/' ---- --
-- >>> debugPrint $ mkRegMultilineComment "<!--" "-->" -- {"<!--"}(char-'-')*'-'((char-'-')+'-')*'-'((char-["->"])(char-'-')*'-'((char-'-')+'-')*'-'|'-')*'>' --mkRegMultilineComment :: String -> String -> Regex -- | Converting back to and forth from LBNF regular regular expression. module BNFC.Check.Regex -- | Convert LBNF regular expression into internal format. normRegex :: Reg -> Regex -- | Convert from internal format to LBNF regular expression. class ReifyRegex a reifyRegex :: ReifyRegex a => a -> Reg instance BNFC.Check.Regex.ReifyRegex BNFC.Types.Regex.CharClassUnion instance BNFC.Check.Regex.ReifyRegex BNFC.Types.Regex.Regex instance BNFC.Check.Regex.ReifyRegex BNFC.Types.Regex.CharClass module BNFC.Backend.Txt2Tags.Options newtype Txt2TagsBackendOptions TxtOpts :: String -> Txt2TagsBackendOptions [target] :: Txt2TagsBackendOptions -> String txt2tagsOptionsParser :: Parser Txt2TagsBackendOptions module BNFC.Backend.Txt2Tags.State data Txt2TagsBackendState Txt2TagsSt :: GlobalOptions -> Txt2TagsBackendOptions -> Txt2TagsBackendState [globalOpt] :: Txt2TagsBackendState -> GlobalOptions [txtOpts] :: Txt2TagsBackendState -> Txt2TagsBackendOptions module BNFC.Backend.Txt2Tags.InitState txt2tagsInitState :: GlobalOptions -> Txt2TagsBackendOptions -> Except String Txt2TagsBackendState module BNFC.Backend.Latex.InitState latexInitState :: GlobalOptions -> Except String LatexBackendState -- | Haskell's reserved words. module BNFC.Backend.Haskell.Utilities.ReservedWords hsReservedWords :: [String] -- | Modifier to avoid clashes in definition. avoidReservedWords :: String -> String avoidReservedWordsArgs :: String -> String avoidReservedWords' :: String1 -> String avoidReservedWordsArgs' :: String1 -> String avoidReservedWords1 :: String1 -> String1 module BNFC.Backend.Haskell.Options data HaskellBackendOptions HaskellOpts :: Maybe String -> Bool -> TokenText -> Bool -> Bool -> Bool -> Bool -> Bool -> HaskellBackendOptions [nameSpace] :: HaskellBackendOptions -> Maybe String [inDir] :: HaskellBackendOptions -> Bool [tokenText] :: HaskellBackendOptions -> TokenText [functor] :: HaskellBackendOptions -> Bool [generic] :: HaskellBackendOptions -> Bool [xml] :: HaskellBackendOptions -> Bool [xmlt] :: HaskellBackendOptions -> Bool [gadt] :: HaskellBackendOptions -> Bool haskellOptionsParser :: Parser HaskellBackendOptions tokenTextReader :: ReadM TokenText showTokenText :: TokenText -> String -- | How to represent token content in the Haskell backend? data TokenText -- | Represent strings as String. StringToken :: TokenText -- | Represent strings as Data.Text. TextToken :: TokenText isStringToken :: TokenText -> Bool isTextToken :: TokenText -> Bool printHaskellOptions :: HaskellBackendOptions -> String instance GHC.Show.Show BNFC.Backend.Haskell.Options.TokenText instance GHC.Classes.Ord BNFC.Backend.Haskell.Options.TokenText instance GHC.Classes.Eq BNFC.Backend.Haskell.Options.TokenText instance GHC.Enum.Enum BNFC.Backend.Haskell.Options.TokenText instance GHC.Enum.Bounded BNFC.Backend.Haskell.Options.TokenText module BNFC.Backend.Common.Utils -- | The name of a module, e.g. Foo.Abs, Foo.Print etc. type ModuleName = String -- | Generalization of unless. unless :: Monoid m => Bool -> m -> m -- | Generalization of when. when :: Monoid m => Bool -> m -> m prPrec :: Int -> Int -> Doc () -> Doc () docToString :: LayoutOptions -> Doc () -> String -- | Replace all occurences of a value by another value replace :: (Eq a, Functor f) => a -> a -> f a -> f a module BNFC.Backend.Haskell.GADT.ComposOp composOp :: ModuleName -> String composOpDoc :: ModuleName -> Doc () module BNFC.Backend.Common.StringUtils -- | Helper function that escapes characters in strings >>> -- escapeChars "\" "\\" >>> escapeChars """ "\"" >>> -- escapeChars "'" "\'" escapeChars :: String -> String fstCharUpper :: String -> String fstCharLower :: String -> String -- | The internal representation of LBNF grammars. -- -- Pragmas have been desugared as far as possible. module BNFC.CF -- | The internal representation of a LBNF grammar. -- -- The name is an abbreviation of Context-Free (Grammar). -- -- Rules are stored in: -- --
-- Ident --IdentCat :: IdentCat -> BaseCat -- | User-defined token category. TokenCat :: CatName -> BaseCat -- | Base category defined by CFG, like Exp. BaseCat :: CatName -> BaseCat -- | Built-in token categories with special token representation. data BuiltinCat -- |
-- Char --BChar :: BuiltinCat -- |
-- Double --BDouble :: BuiltinCat -- |
-- Integer --BInteger :: BuiltinCat -- |
-- String --BString :: BuiltinCat -- | Built-in token Ident, treated as a string. data IdentCat -- |
-- Ident --BIdent :: IdentCat -- | Types are categories without the precedences (CoerceCat). data Type -- | Base category. BaseType :: BaseCat -> Type -- | List category. ListType :: Type -> Type -- | Function type t(t₁,...,tₙ) or t₁ → ... → tₙ → t. data FunType FunType :: Type -> [Type] -> FunType -- | Result type. [targetType] :: FunType -> Type -- | Types of parameters, left to right. [argTypes] :: FunType -> [Type] -- | Bodies of Function. For convenience, these are fully typed. data Exp -- | (Possibly defined) label with its type applied to the correct number -- of expressions. App :: Label -> FunType -> [Exp] -> Exp -- | Use of function parameter. Var :: Parameter -> Exp LitInteger :: Integer -> Exp LitDouble :: Double -> Exp LitChar :: Char -> Exp LitString :: String -> Exp -- | Bound variable. data Parameter Parameter :: VarName -> Type -> Parameter [paramName] :: Parameter -> VarName [paramType] :: Parameter -> Type type VarName = String1 -- | Definition body of a constructor. data Function Function :: [Parameter] -> Exp -> Type -> Function [funPars] :: Function -> [Parameter] [funBody] :: Function -> Exp [funType] :: Function -> Type -- | Label names are nonempty strings. type LabelName = String1 -- | LBNF rule label (AST constructor). data Label -- | ordinary rule label (uppercase) LId :: LabelName -> Label -- | defined label (lowercase) No representation in AST: LDef :: LabelName -> Label -- | coercion _ List labels, mapped to the list constructors of -- the target language. LWild :: Label -- | empty list [] LNil :: Label -- | singleton list (:[]) ("robot gorilla") LSg :: Label -- | list constructor (:) LCons :: Label -- | Element of a rule right hand side (rhs). data Item' a -- | Keyword or symbol (not represented in AST). Terminal :: a -> Item' a -- | Category (represented in AST). NTerminal :: Cat -> Item' a type AItem = Item' String1 " AST/printer flavor." type Item = Item' Keyword " Parser flavor." -- | The bare rhs of a rule. type RHS' a = [Item' a] type ARHS = RHS' String1 type RHS = RHS' Keyword -- | The origin of a rule. data RuleOrigin -- | Ordinary LBNF rule. FromOrdinary :: RuleOrigin -- | Expanded from rules pragma. FromRules :: RuleOrigin -- | Expanded from coercions pragma. FromCoercions :: RuleOrigin -- | Expanded from list pragma: separator or terminator. FromList :: RuleOrigin -- | The AST-flavor representation of the rule rhs with meta information. data ARuleRHS ARuleRHS :: RuleOrigin -> Parseable -> ARHS -> ARuleRHS -- | A rule can also originate from pragmas. [aruleOrigin] :: ARuleRHS -> RuleOrigin -- | internal or parseable? [aruleParseable] :: ARuleRHS -> Parseable -- | Right hand side. [aruleRHS] :: ARuleRHS -> ARHS -- | The parser-flavor representation of the rule label with meta -- information. data RuleLabel RuleLabel :: RuleOrigin -> Label -> RuleLabel -- | A rule can also originate from pragmas. [ruleOrigin] :: RuleLabel -> RuleOrigin -- | The name of the rule. [ruleLabel] :: RuleLabel -> Label data Separator' a -- | E.g. separator _ ",". Separator :: a -> Separator' a -- | E.g. terminator _ ";". The last case is better represented as -- Nothing. -- | NoSeparator -- -- ^ E.g. separator _ -- "" or terminator _ "". Terminator :: a -> Separator' a type ASeparator = Separator' String1 type Separator = Separator' Keyword -- | Is a rule relevant for the parser or only for the AST/printer? data Parseable -- | internal rule (only for AST & printer) Internal :: Parseable -- | ordinary rule (also for parser) Parseable :: Parseable -- | Does a token category carry position information? data PositionToken -- | from 'position token' pragma PositionToken :: PositionToken -- | from ordinary token pragma NoPositionToken :: PositionToken lbnfTokenDefs :: Lens' LBNF TokenDefs lbnfSymbolsKeywords :: Lens' LBNF SymbolsKeywords lbnfSymbols :: Lens' LBNF SymbolUses lbnfSignature :: Lens' LBNF Signature lbnfParserRules :: Lens' LBNF ParserRules lbnfParserBuiltins :: Lens' LBNF UsedBuiltins lbnfLineComments :: Lens' LBNF LineComments lbnfLayoutTop :: Lens' LBNF (Maybe Position) lbnfLayoutStop :: Lens' LBNF LayoutKeywords lbnfLayoutStart :: Lens' LBNF LayoutKeywords lbnfKeywords :: Lens' LBNF KeywordUses lbnfFunctions :: Lens' LBNF Functions lbnfEntryPoints :: Lens' LBNF EntryPoints lbnfBlockComments :: Lens' LBNF BlockComments lbnfASTRulesAP :: Lens' LBNF ASTRulesAP lbnfASTRules :: Lens' LBNF ASTRules lbnfASTBuiltins :: Lens' LBNF UsedBuiltins -- | Convert Cat to Type, converting CoerceCat to -- BaseCat. catToType :: Cat -> Type catToIdentifier :: Cat -> String1 baseCatToIdentifier :: BaseCat -> String1 -- | Print CatName from Cat in AST generator. printCatName :: Cat -> String printCatNamePrec :: Cat -> String printCatNamePrec' :: Cat -> String catToString :: Cat -> String printBaseCatName :: BaseCat -> String -- | is Cat coerced? isCatCoerced :: Cat -> Bool -- | is Cat list category? isCatList :: Cat -> Bool -- | is Cat between used builtins. isCatBuiltin :: Cat -> Bool -- | get Cat coercion number, returns 0 if Cat is not -- coerced. getCatPrec :: Cat -> Integer -- | 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 isBuiltin :: BaseCat -> Bool isIdentifier :: BaseCat -> Bool isToken :: BaseCat -> Bool builtinCats :: [(BuiltinCat, String1)] printBuiltinCat :: BuiltinCat -> String1 printIdentCat :: IdentCat -> String1 parseBuiltinCat :: String1 -> Maybe (Either IdentCat BuiltinCat) identBuiltinCats :: [(Either IdentCat BuiltinCat, String1)] tChar :: Type tDouble :: Type tInteger :: Type tString :: Type printTypeName :: Type -> String -- | When given a list Type, i.e. '[C]', it removes the square brackets, -- and adds the prefix List, i.e. ListC. (for Happy and Latex) identType :: Type -> String isListType :: Type -> Bool isBuiltinType :: Type -> Bool isIdentType :: Type -> Bool isTokenType :: Type -> Bool labelFromIdentifier :: LabelName -> Label -- | Print Label name. printLabelName :: Label -> String printRuleName :: Label -> String isDef :: Label -> Bool isCoercion :: Label -> Bool isList :: Label -> Bool isALabel :: Label -> Bool isPLabel :: Label -> Bool -- | Filter Labels that will be printed in the AST datatypes. filterLabelsAST :: [String] -> [(Label, ([Type], (Integer, ARHS)))] -> [(Label, ([Type], (Integer, ARHS)))] -- | Filter Labels that will be printed in the Pretty printer. filterLabelsPrinter :: [String] -> [(Label, ([Type], (Integer, ARHS)))] -> [(Label, ([Type], (Integer, ARHS)))] -- | Print names of Cat in a rhs. printRhsCats :: [Item' a] -> [String] -- | Print rhs Items, both non terminals and terminals. printRHS :: [Item' Keyword] -> [String] -- | Get Cats in a rhs. getRhsCats :: [Item' a] -> [Cat] printItemName :: Item' String1 -> String isNTerminal :: Item' a -> Bool isItemListCat :: Item' a -> Bool isItemBuiltin :: Item' a -> Bool -- | Get the non-terminals of a rhs in left-to-right order. rhsCats :: RHS' a -> [Cat] -- | Get the types of a rhs. rhsType :: RHS' a -> [Type] -- | does a token definition contain a no position token. isNoPositionToken :: WithPosition TokenDef -> Bool -- | does a token definition contain (with position) a position token. isPositionToken :: WithPosition TokenDef -> Bool -- | does a token definition contain a position token. isPosToken :: TokenDef -> Bool hasIdentifier :: TokenDefs -> Bool -- | Print Exp (function body in define pragma). printExp :: Bool -> String -> Exp -> String printExp1 :: Exp -> String printExp2 :: String -> Exp -> String isApp1 :: Exp -> Bool isApp2 :: Exp -> Bool -- | All-whitespace strings (in particular, empty strings) give -- Nothing. getKeyword :: Separator -> Keyword parseKeyword :: String -> Maybe Keyword parseASeparator :: Separator' String -> Maybe ASeparator trimSeparator :: ASeparator -> Maybe Separator lookupRHS :: Cat -> RHS -> ParserRules -> Maybe (WithPosition RuleLabel) layoutsAreUsed :: LBNF -> Bool instance GHC.Classes.Ord BNFC.CF.Keyword instance GHC.Classes.Eq BNFC.CF.Keyword instance GHC.Classes.Ord BNFC.CF.Symbol instance GHC.Classes.Eq BNFC.CF.Symbol instance GHC.Show.Show BNFC.CF.LineComment instance GHC.Show.Show BNFC.CF.BlockComment instance GHC.Show.Show a => GHC.Show.Show (BNFC.CF.Cat' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.CF.Cat' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.CF.Cat' a) instance GHC.Enum.Enum BNFC.CF.BuiltinCat instance GHC.Enum.Bounded BNFC.CF.BuiltinCat instance GHC.Show.Show BNFC.CF.BuiltinCat instance GHC.Classes.Ord BNFC.CF.BuiltinCat instance GHC.Classes.Eq BNFC.CF.BuiltinCat instance GHC.Show.Show BNFC.CF.IdentCat instance GHC.Classes.Ord BNFC.CF.IdentCat instance GHC.Classes.Eq BNFC.CF.IdentCat instance GHC.Show.Show BNFC.CF.BaseCat instance GHC.Classes.Ord BNFC.CF.BaseCat instance GHC.Classes.Eq BNFC.CF.BaseCat instance GHC.Show.Show BNFC.CF.Type instance GHC.Classes.Ord BNFC.CF.Type instance GHC.Classes.Eq BNFC.CF.Type instance GHC.Show.Show BNFC.CF.FunType instance GHC.Classes.Eq BNFC.CF.FunType instance GHC.Show.Show BNFC.CF.Parameter instance GHC.Show.Show BNFC.CF.Label instance GHC.Classes.Ord BNFC.CF.Label instance GHC.Classes.Eq BNFC.CF.Label instance GHC.Show.Show BNFC.CF.Exp instance GHC.Show.Show BNFC.CF.Function instance Data.Traversable.Traversable BNFC.CF.Item' instance Data.Foldable.Foldable BNFC.CF.Item' instance GHC.Base.Functor BNFC.CF.Item' instance GHC.Show.Show a => GHC.Show.Show (BNFC.CF.Item' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.CF.Item' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.CF.Item' a) instance GHC.Show.Show BNFC.CF.RuleOrigin instance GHC.Classes.Ord BNFC.CF.RuleOrigin instance GHC.Classes.Eq BNFC.CF.RuleOrigin instance GHC.Show.Show BNFC.CF.RuleLabel instance GHC.Classes.Eq BNFC.CF.RuleLabel instance Data.Traversable.Traversable BNFC.CF.Separator' instance Data.Foldable.Foldable BNFC.CF.Separator' instance GHC.Base.Functor BNFC.CF.Separator' instance GHC.Show.Show a => GHC.Show.Show (BNFC.CF.Separator' a) instance GHC.Classes.Ord a => GHC.Classes.Ord (BNFC.CF.Separator' a) instance GHC.Classes.Eq a => GHC.Classes.Eq (BNFC.CF.Separator' a) instance GHC.Show.Show BNFC.CF.Parseable instance GHC.Classes.Ord BNFC.CF.Parseable instance GHC.Classes.Eq BNFC.CF.Parseable instance GHC.Show.Show BNFC.CF.ARuleRHS instance GHC.Classes.Eq BNFC.CF.ARuleRHS instance GHC.Show.Show BNFC.CF.PositionToken instance GHC.Classes.Ord BNFC.CF.PositionToken instance GHC.Classes.Eq BNFC.CF.PositionToken instance GHC.Show.Show BNFC.CF.TokenDef instance GHC.Show.Show BNFC.CF.LBNF instance GHC.Show.Show BNFC.CF.Symbol instance GHC.Show.Show BNFC.CF.Keyword -- | The checker monad. -- -- Responsible for throwing errors and accumulating warnings. module BNFC.Check.Monad -- | Monad for error reporting and warnings. class Monad m => MonadCheck m fatalError :: MonadCheck m => FatalError -> m a recoverableError :: MonadCheck m => RecoverableError -> m () warn :: MonadCheck m => Warning -> m () -- | Set the file position for subsequent errors. atPosition :: (MonadCheck m, ToPosition' p) => p -> m a -> m a -- | Retrieve the stored position. askPosition :: MonadCheck m => m Position' fatalError :: (MonadCheck m, MonadTrans t, MonadCheck n, t n ~ m) => FatalError -> m a recoverableError :: (MonadCheck m, MonadTrans t, MonadCheck n, t n ~ m) => RecoverableError -> m () warn :: (MonadCheck m, MonadTrans t, MonadCheck n, t n ~ m) => Warning -> m () -- | Set the file position for subsequent errors. atPosition :: (MonadCheck m, MonadTransControl t, MonadCheck n, t n ~ m) => ToPosition' p => p -> m a -> m a -- | Retrieve the stored position. askPosition :: (MonadCheck m, MonadTrans t, MonadCheck n, t n ~ m) => m Position' -- | Fatal errors (check cannot continue). data FatalError FatalError :: FatalError -- | The given label isn't contained in the Signature. UndefinedLabel :: LabelName -> FatalError -- | A list expression was found at the given type, which isn't a -- ListType. ListsDontInhabitType :: Type -> FatalError -- | Any of these errors allows to continue BNFC, but may result in -- undesired/illformed output. data RecoverableError -- | The pragma delimiters has been removed in BNFC 2.9. Pragma is -- ignored. DelimitersNotSupported :: RecoverableError -- | E.g. trying to mix ordinary rules with list pragmas or token -- definitions. Redefinition is ignored. IncompatibleDefinition :: ICat -> Position -> RecoverableError -- | Trying to apply coercions pragma to a CoerceCat, e.g. -- coercions Exp3 2. Pragma is ignored. Pass 2 errors CoercionsOfCoerceCat :: RecoverableError -- | Trying to apply coercions pragma to a BuiltinCat, e.g. -- coercions Integer 2. Pragma is ignored. CoercionsOfBuiltinCat :: RecoverableError -- | Trying to apply coercions pragma to a IdentCat, e.g. -- coercions Ident 2. Pragma is ignored. CoercionsOfIdentCat :: RecoverableError -- | Trying to apply coercions pragma to a TokenCat, e.g. -- coercions Id 2. Pragma is ignored. CoercionsOfTokenCat :: RecoverableError -- | This base category is not defined. UnknownCatName :: CatName -> RecoverableError -- | Tried to make a precedence variant of a builtin category, like -- Char3. CoerceBuiltinCat :: BuiltinCat -> RecoverableError -- | Tried to make a precedence variant of an ident category, like -- Ident3. CoerceIdentCat :: IdentCat -> RecoverableError -- | Tried to make a precedence variant of a list category, like -- [Arg3]. CoerceListCat :: CatName -> RecoverableError -- | Tried to make a precedence variant of a token category, like -- Id3. CoerceTokenCat :: CatName -> RecoverableError -- | The label LabelName has been defined already, at -- Position. DuplicateLabel :: LabelName -> Position -> RecoverableError -- | The same BNF rule already exists, at Position. DuplicateRHS :: Position -> RecoverableError -- | Cannot use ordinary or defined labels to construct a list category. InvalidListRule :: LabelName -> RecoverableError -- | List label to construct non-list category. InvalidListLabel :: Type -> RecoverableError -- | Invalid type for label []. InvalidLabelNil :: FunType -> RecoverableError -- | Invalid type for label (:). InvalidLabelCons :: FunType -> RecoverableError -- | Invalid type for label (:[]). InvalidLabelSg :: FunType -> RecoverableError -- | Invalid type for label _. InvalidLabelWild :: FunType -> RecoverableError -- | define pragma with unused label is skipped, since we don't -- have its type. IgnoringUndeclaredFunction :: RecoverableError -- | Type checker added missing parameters in a define. NotEnoughParameters :: List1 String1 -> RecoverableError -- | These parameters were ignored since they are too many, according to -- the type. DroppingSpuriousParameters :: List1 Arg -> RecoverableError -- | A constructor/function misses arguments of the given types. MissingArguments :: LabelName -> List1 Type -> RecoverableError -- | A constructor/function was given (these) more arguments than needed. DroppingSpuriousArguments :: LabelName -> List1 Exp -> RecoverableError -- | An expression of the first type was expected, but it has the second -- type. ExpectedVsInferredType :: Type -> Type -> RecoverableError -- | Defined token category matches the empty string. Such a token -- can be produced by the lexer when nothing else can be produced, but -- then it can be produced infinitely often without making progress. This -- may result in a loop in the lexer. Token definition is kept. NullableToken :: CatName -> Regex -> RecoverableError -- | One of the delimiters of a block comment is empty. IllformedBlockComment :: RecoverableError -- | A keyword appears both in layout and layout stop. -- The redefinition is ignored. Final checks ConflictingUsesOfLayoutKeyword :: Keyword -> Position -> RecoverableError -- | No entrypoints have been defined. This is an error that does not block -- any other checks, so it is "recoverable". But it makes flags failure -- of the check phase, because later phases (e.g. parser generation) will -- crash. EmptyGrammar :: RecoverableError -- | Any of these warnings drops the useless or redundant definition. data Warning FooWarning :: Warning -- | The label LabelName clashes with a category of the same name -- defined at Position. LabelClashesWithCategory :: LabelName -> Position -> Warning -- | coercions _ 0 does not add any rules. IgnoringNullCoercions :: Warning -- | A list rule with different coercion levels of the base category. -- Cannot implement faithful printer for such rules. NonUniformListRule :: Cat -> [Cat] -> Warning -- | Grammar permits upper case parameters, but this isn't Haskell-style -- (which is the model for BNFC's expression syntax otherwise). ParameterShouldBeLowerCase :: VarName -> Warning -- | A parameter shadows a previous one. ShadowingParameter :: VarName -> Warning -- | The given label is shadowed by a parameter, which looks confusing. ShadowedByParameter :: VarName -> Warning -- | Defined token category may not match anything. EmptyToken :: CatName -> Regex -> Warning -- | comment "" is ignored. IgnoringEmptyLineComment :: Warning -- | comment "" "" is ignored. IgnoringEmptyBlockComment :: Warning -- | layout [stop] "" is simply ignored EmptyLayoutKeyword :: Warning -- | layout [stop] kw but kw is not mentioned in the -- grammar. UndefinedLayoutKeyword :: Keyword -> Warning -- | This layout keyword already occurred in a pragma of the same kind. DuplicateLayoutKeyword :: Keyword -> Position -> Warning -- | layout toplevel already appeared at Position. DuplicateLayoutTop :: Position -> Warning -- | Intermediated form of categories. (No builtins/token types recognized -- yet.) type ICat = Cat' CatName type PFatalError = WithPosition' FatalError type PRecoverableError = WithPosition' RecoverableError type PWarning = WithPosition' Warning type PWarnErr = WithPosition' (Either RecoverableError Warning) type RecoverableErrors = [PRecoverableError] type Warnings = [PWarning] type WarnErrs = [PWarnErr] -- | The LBNF checker monad. newtype Check a Check :: ReaderT Position' (ExceptT PFatalError (Writer WarnErrs)) a -> Check a [unCheck] :: Check a -> ReaderT Position' (ExceptT PFatalError (Writer WarnErrs)) a runCheck :: Check a -> (Warnings, RecoverableErrors, Either PFatalError a) instance GHC.Show.Show BNFC.Check.Monad.FatalError instance GHC.Show.Show BNFC.Check.Monad.Warning instance GHC.Show.Show BNFC.Check.Monad.RecoverableError instance GHC.Base.Monad BNFC.Check.Monad.Check instance GHC.Base.Applicative BNFC.Check.Monad.Check instance GHC.Base.Functor BNFC.Check.Monad.Check instance BNFC.Check.Monad.MonadCheck BNFC.Check.Monad.Check instance BNFC.Check.Monad.MonadCheck m => BNFC.Check.Monad.MonadCheck (Control.Monad.Trans.Except.ExceptT e m) instance BNFC.Check.Monad.MonadCheck m => BNFC.Check.Monad.MonadCheck (Control.Monad.Trans.Reader.ReaderT r m) instance BNFC.Check.Monad.MonadCheck m => BNFC.Check.Monad.MonadCheck (Control.Monad.Trans.State.Lazy.StateT s m) -- | First pass of processing a LBNF file. -- --
-- _. Exp ::= Exp1; -- _. Exp1 ::= Exp2; -- _. Exp2 ::= Exp3; -- _. Exp3 ::= "(" Exp ")"; --checkCoercions :: Position -> Identifier -> Integer -> M () -- | Add rules from rules pragma. checkRules :: Position -> Identifier -> [RHS] -> M () checkDefine :: Position -> Identifier -> [Arg] -> Exp -> M () -- | Add a token category (position carrying or not) defined by a regular -- expression. addTokenDef :: Position -> Identifier -> PositionToken -> Reg -> M () -- | Add a keyword that starts or stops layout. addLayoutKeyword :: Lens' LBNF LayoutKeywords -> Lens' LBNF LayoutKeywords -> Position -> String -> M () -- | Add line comment delimiter, unless empty. addLineComment :: Position -> String -> M () -- | Add block comment delimiters if both are non-empty. addBlockComment :: Position -> String -> String -> M () -- | Entrypoint for the LBNF checker. module BNFC.Check.Run checkGrammar :: Grammar -> (Warnings, RecoverableErrors, Either PFatalError LBNF) -- | Utilies for the Haskell pretty printer. module BNFC.Backend.Haskell.Utilities.Printer cats :: [Type] -> [String] listcats :: [Type] -> [String] toks :: LBNF -> [String] keywords :: LBNF -> [String] data Literal LitChar :: Literal LitString :: Literal LitInteger :: Literal LitDouble :: Literal literalDoc :: Doc () tokenDoc :: [String] -> Doc () catDoc :: [String] -> Doc () listcatDoc :: [String] -> Doc () annDoc :: Doc () -- | Annotate keywords with Magenta color. annotateKeyword :: Doc () -- | Annotate literals with Cyan color. annotateLiteral :: Doc () -- | Annotate tokens with Green color. annotateToken :: Doc () annotateCategory :: Doc () annotateListCategory :: Doc () printAnn :: [String] -> [String] -> [String] -> Doc () parseType :: Type -> Doc () parseTokenName :: CatName -> Doc () annotations :: [Item' String1] -> [String] annToAnsiStyle :: Doc () renderFunction :: Doc () module BNFC.Backend.Haskell.Utilities.Parser tokenName :: Doc () parserCatName :: Cat -> Doc () generateP :: Bool -> Cat -> Doc () qualify :: String -> String -> String -- | Generate patterns and a set of metavariables (de Bruijn indices) -- indicating where in the pattern the non-terminals are locate. -- --
-- >>> generatePatterns False [ NTerminal (Cat' (BaseCat 'E':|"xp")), Terminal (Keyword ('+':|[])), NTerminal (Cat' (BaseCat 'E':|"xp")) ] -- ("Exp '+' Exp",["$1","$3"]) ---- --
-- >>> generatePatterns True [ NTerminal (Cat' (BaseCat 'E':|"xp")), Terminal (Keyword ('+':|[])), NTerminal (Cat' (BaseCat 'E':|"xp")) ] -- ("Exp '+' Exp",["(snd $1)","(snd $3)"]) --generatePatterns :: Bool -> RHS -> (String, [String]) module BNFC.Backend.CommonInterface.OOAbstractSyntax data Abs Abs :: [String] -> [String] -> [String] -> [String] -> Signature -> Functions -> Abs [posTokens] :: Abs -> [String] [noPosTokens] :: Abs -> [String] [catClasses] :: Abs -> [String] [labelClasses] :: Abs -> [String] [signatures] :: Abs -> Signature [defineds] :: Abs -> Functions lbnf2abs :: LBNF -> Abs allClasses :: LBNF -> [String] allNonClasses :: LBNF -> [String] basetypes :: [([Char], [Char])] classVar :: String -> String pointerIf :: Bool -> String -> String module BNFC.Backend.CommonInterface.NamedVariables type IVar = (String, Int) -- | 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] fixCoersions :: ASTRules -> ASTRules varName :: [Char] -> [Char] showNum :: (Eq a, Num a, Show a) => a -> [Char] firstLowerCase :: String -> String module BNFC.Backend.CommonInterface.Backend type Result = [(FilePath, String)] type Log = Writer String type Output = WriterT Result Log () -- | Backend typeclass. class Backend (target :: TargetLanguage) where { type family BackendOptions target; type family BackendState target; } parseOpts :: Backend target => Parser (BackendOptions target) initState :: Backend target => LBNF -> GlobalOptions -> BackendOptions target -> Except String (BackendState target) abstractSyntax :: Backend target => LBNF -> State (BackendState target) Result printer :: Backend target => LBNF -> State (BackendState target) Result lexer :: Backend target => LBNF -> State (BackendState target) Result parser :: Backend target => LBNF -> State (BackendState target) Result parserTest :: Backend target => LBNF -> State (BackendState target) Result makefile :: Backend target => LBNF -> State (BackendState target) Result runBackend :: forall target. Backend target => GlobalOptions -> BackendOptions target -> LBNF -> Except String Result module BNFC.Backend.Txt2Tags.Txt2Tags txt2tags :: LBNF -> State Txt2TagsBackendState Result cf2string :: LBNF -> String -> String cf2doc :: LBNF -> String -> Doc () introduction :: String -> Doc () printTerminals :: LBNF -> String -> Doc () printBuiltin :: BuiltinCat -> Doc () reservedWords :: Doc () printKeywords :: String -> [String] -> Doc () printSymbols :: String -> [String] -> Doc () printComments :: [String] -> [(String, String)] -> Doc () printToken :: (CatName, WithPosition TokenDef) -> Doc () printGrammar :: LBNF -> String -> Doc () printRule :: (Cat, [ARHS]) -> Doc () printARHS :: ARHS -> Doc () printItem :: Item' String1 -> Doc () printCat :: Cat -> String printRegTxt2Tags :: Regex -> Doc () class Print a prt :: Print a => Int -> a -> Doc () instance BNFC.Backend.Txt2Tags.Txt2Tags.Print a => BNFC.Backend.Txt2Tags.Txt2Tags.Print [a] instance BNFC.Backend.Txt2Tags.Txt2Tags.Print GHC.Types.Char instance BNFC.Backend.Txt2Tags.Txt2Tags.Print BNFC.Types.Regex.Regex instance BNFC.Backend.Txt2Tags.Txt2Tags.Print BNFC.Types.Regex.CharClassUnion instance BNFC.Backend.Txt2Tags.Txt2Tags.Print BNFC.Types.Regex.CharClassAtom module BNFC.Backend.Txt2Tags.Makefile txt2tagsmakefile :: LBNF -> State Txt2TagsBackendState Result makefileString :: String -> String -> String makefileDoc :: String -> String -> Doc () module BNFC.Backend.Txt2Tags instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetTxt2Tags module BNFC.Backend.OCaml newtype OcamlBackendOptions OcamlOpts :: Bool -> OcamlBackendOptions ocamlOptionsParser :: Parser OcamlBackendOptions data OcamlBackendState instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetOCaml module BNFC.Backend.Latex.Makefile latexmakefile :: LBNF -> State LatexBackendState Result makefileString :: String -> String makefileDoc :: String -> Doc () module BNFC.Backend.Latex.Latex latex :: LBNF -> State LatexBackendState Result cf2string :: LBNF -> String -> String cf2doc :: LBNF -> String -> Doc () beginning :: String -> Doc () macros :: Doc () printTerminals :: LBNF -> String -> Doc () printBuiltin :: BuiltinCat -> Doc () printToken :: (CatName, WithPosition TokenDef) -> Doc () reservedWords :: Doc () tabular :: Doc () -> Doc () printKeywords :: String -> [String] -> Doc () reserved :: String -> Doc () printSymbols :: String -> [String] -> Doc () symbol :: String -> Doc () printEscape :: String -> String printComments :: [String] -> [(String, String)] -> Doc () printGrammar :: LBNF -> String -> Doc () printRule :: (Cat, [ARHS]) -> Doc () terminal :: String1 -> Doc () nonterminal :: Cat -> Doc () printItem :: Item' String1 -> Doc () printARHS :: ARHS -> Doc () printRegLatex :: Regex -> Doc () class Print a prt :: Print a => Int -> a -> Doc () instance BNFC.Backend.Latex.Latex.Print a => BNFC.Backend.Latex.Latex.Print [a] instance BNFC.Backend.Latex.Latex.Print GHC.Types.Char instance BNFC.Backend.Latex.Latex.Print BNFC.Types.Regex.Regex instance BNFC.Backend.Latex.Latex.Print BNFC.Types.Regex.CharClassUnion instance BNFC.Backend.Latex.Latex.Print BNFC.Types.Regex.CharClassAtom module BNFC.Backend.Latex data LatexBackendOptions LatexOpts :: LatexBackendOptions latexOptionsParser :: Parser LatexBackendOptions instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetLatex module BNFC.Backend.Java data JavaBackendOptions JavaOpts :: Bool -> Maybe String -> Bool -> Bool -> Bool -> JavaBackendOptions [lineNumbers] :: JavaBackendOptions -> Bool [nameSpace] :: JavaBackendOptions -> Maybe String [jlex] :: JavaBackendOptions -> Bool [jflex] :: JavaBackendOptions -> Bool [antlr4] :: JavaBackendOptions -> Bool javaOptionsParser :: Parser JavaBackendOptions data JavaBackendState instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetJava -- | Backend write module. -- -- Defines useful functions to write the backend output to files. module BNFC.Backend.CommonInterface.Write writeFiles :: FilePath -> Result -> IO () module BNFC.Backend.CommonInterface.Types module BNFC.Backend.Haskell.Utilities.Utils -- | Token data type for lexer and parser specification generation. data Token Builtin :: BuiltinCat -> Token Identifier :: Token UserDefined :: CatName -> Token printTokenName :: Token -> String tokenTextImport :: TokenText -> Doc () tokenTextType :: TokenText -> Doc () tokenTextPack :: TokenText -> String -> String tokenTextPackParens :: TokenText -> String -> Doc () tokenTextUnpack :: TokenText -> String -> Doc () -- | Make a variable name for a category. catToVarName :: Cat -> String -- | Turn (non-terminal) items into indexed variables. indexVars :: [Item' String1] -> [(String, Integer)] printArgs :: ARHS -> [Doc ()] posType :: String posConstr :: String noPosConstr :: String -- | Make directory of generated files. mkDir :: Bool -> Maybe String -> String -> String -> String -- | Relative filepath where to write generated components. mkFilePath :: Bool -> Maybe String -> String -> String -> String -> FilePath -- | Make module name of generated files. mkModule :: Bool -> Maybe String -> String -> String -> String instance GHC.Show.Show BNFC.Backend.Haskell.Utilities.Utils.Token -- | Utilies for the Haskell lexer specification. module BNFC.Backend.Haskell.Utilities.Lexer tokenName :: Token -> Doc () tokenComment :: Token -> Doc () isUserDefined :: Token -> Bool unicodeAndSymbols :: LBNF -> [String] asciiKeywords :: LBNF -> [String] -- | Utilies for Haskell state initialitation. module BNFC.Backend.Haskell.Utilities.InitState -- | Get grammar tokens for lexer specification generation. getTokens :: LBNF -> [Token] -- | Sort functions (define pragma) and avoid reserved words. processFunctions :: Functions -> [(LabelName, Function)] -- | Sort parser rules and avoid reserved words. processParserRules :: ParserRules -> [(Cat, Map RHS RuleLabel)] -- | Process AST rules to generate Abstract Syntax and Printer. processRules :: ASTRulesAP -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -- | Sort tokens (token pragma) according to their definition order in the -- .cf file. sortTokens :: TokenDefs -> [(CatName, TokenDef)] module BNFC.Backend.Haskell.State data HaskellBackendState HaskellSt :: GlobalOptions -> HaskellBackendOptions -> [Token] -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(Cat, Map RHS RuleLabel)] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> HaskellBackendState [globalOpt] :: HaskellBackendState -> GlobalOptions [haskellOpts] :: HaskellBackendState -> HaskellBackendOptions [lexerParserTokens] :: HaskellBackendState -> [Token] [astRules] :: HaskellBackendState -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] [parserRules] :: HaskellBackendState -> [(Cat, Map RHS RuleLabel)] [functions] :: HaskellBackendState -> [(LabelName, Function)] [tokens] :: HaskellBackendState -> [(CatName, TokenDef)] module BNFC.Backend.Haskell.Test haskellParserTest :: LBNF -> State HaskellBackendState Result cf2test :: LBNF -> String -> TokenText -> Bool -> Maybe String -> String cf2doc :: LBNF -> String -> TokenText -> Bool -> Maybe String -> Doc () module BNFC.Backend.Haskell.Template haskellTemplate :: LBNF -> State HaskellBackendState Result cf2template :: [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [CatName] -> String -> Bool -> Maybe String -> Bool -> String cf2doc :: [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [CatName] -> String -> Bool -> Maybe String -> Bool -> Doc () prologue :: ModuleName -> ModuleName -> Bool -> Bool -> Doc () printTokens :: ModuleName -> [CatName] -> Doc () printToken :: ModuleName -> CatName -> Doc () printDatas :: ModuleName -> Bool -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> Doc () printData :: ModuleName -> Bool -> Type -> [(Label, ([Type], (Integer, ARHS)))] -> Doc () printCase :: ModuleName -> Bool -> (Label, ARHS) -> Doc () module BNFC.Backend.Haskell.InitState haskellInitState :: LBNF -> GlobalOptions -> HaskellBackendOptions -> Except String HaskellBackendState -- | Checks specific of the Haskell language. hsChecks :: LBNF -> Except String () module BNFC.Backend.Haskell.Printer haskellPrinter :: LBNF -> State HaskellBackendState Result cf2printer :: LBNF -> String -> Bool -> Maybe String -> Bool -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(CatName, TokenDef)] -> Bool -> TokenText -> String cf2doc :: LBNF -> String -> Bool -> Maybe String -> Bool -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(CatName, TokenDef)] -> Bool -> TokenText -> Doc () printPrologue :: LBNF -> String -> Bool -> Maybe String -> Bool -> ModuleName -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> Doc () -- | Print tokens instances for the printer. printTokenInstances :: ModuleName -> TokenText -> [(CatName, TokenDef)] -> Doc () printTokenInstance :: ModuleName -> TokenText -> (CatName, TokenDef) -> Doc () -- | Print cateries instances for the printer. printCatInstances :: ModuleName -> Bool -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> Doc () printCatInstance :: ModuleName -> Bool -> Type -> [(Label, ([Type], (Integer, ARHS)))] -> Doc () printCase :: Doc () -> Bool -> (Label, (Integer, ARHS)) -> (Integer, Doc ()) rhsToPrint :: ARHS -> [Doc ()] module BNFC.Backend.Haskell.Layout cf2layout :: LBNF -> String -> Bool -> Maybe String -> String haskellLayout :: LBNF -> State HaskellBackendState Result module BNFC.Backend.Haskell.GADT.Utils isTreeType :: (Label, ARHS) -> Bool module BNFC.Backend.Haskell.GADT.Template haskellGADTTemplate :: LBNF -> State HaskellBackendState Result module BNFC.Backend.Haskell.AbstractSyntax cf2abs :: LBNF -> String -> Bool -> Maybe String -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> Bool -> Bool -> Bool -> TokenText -> String haskellAbstractSyntax :: LBNF -> State HaskellBackendState Result -- | Print functions given by the define pragma. printFunctions :: Bool -> [(LabelName, Function)] -> Doc () module BNFC.Backend.Haskell.GADT.AbstractSyntax haskellAbstractSyntaxGADT :: LBNF -> State HaskellBackendState Result cf2abs :: LBNF -> String -> Bool -> Maybe String -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> TokenText -> String cf2doc :: LBNF -> String -> Bool -> Maybe String -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> TokenText -> Doc () prologue :: ModuleName -> ModuleName -> Bool -> [String] -> TokenText -> Bool -> Doc () pragmas :: Bool -> Doc () imports :: ModuleName -> Bool -> TokenText -> Doc () printData :: [String] -> Doc () printTree :: [String] -> TokenText -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(CatName, TokenDef)] -> Doc () composInstances :: [(Label, ARHS)] -> Doc () showInstances :: [(Label, ARHS)] -> [(CatName, TokenDef)] -> Doc () eqInstance :: Doc () ordInstance :: Doc () johnMajorEq :: [(Label, ARHS)] -> [(CatName, TokenDef)] -> Doc () indexes :: [(Label, [Type])] -> [String] -> Doc () compareSame :: [(Label, ARHS)] -> [(CatName, TokenDef)] -> Doc () module BNFC.Backend.Haskell.Parser haskellParser :: LBNF -> State HaskellBackendState Result cf2parser :: LBNF -> [(Cat, Map RHS RuleLabel)] -> String -> Bool -> Maybe String -> TokenText -> [Token] -> Bool -> String cf2doc :: LBNF -> [(Cat, Map RHS RuleLabel)] -> String -> Bool -> Maybe String -> TokenText -> [Token] -> Bool -> Doc () header :: ModuleName -> ModuleName -> ModuleName -> TokenText -> [Cat] -> Doc () -- | The declarations of a happy file. >>> declarations False [Cat -- A, Cat B, ListCat (Cat B)] %name pA A %name pB B -- %name pListB ListB -- no lexer declaration %monad { Err } { -- (>>=) } { return } %tokentype {Token} -- --
-- >>> declarations True [Cat "A", Cat "B", ListCat (Cat "B")] -- %name pA_internal A -- %name pB_internal B -- %name pListB_internal ListB -- -- no lexer declaration -- %monad { Err } { (>>=) } { return } -- %tokentype {Token} --declarations :: Bool -> [Cat] -> Doc () -- | Generate the list of tokens and their identifiers. tokensList :: LBNF -> [Token] -> Bool -> Doc () specialRules :: LBNF -> ModuleName -> TokenText -> Bool -> [Token] -> Doc () specialRule :: LBNF -> ModuleName -> TokenText -> Bool -> Token -> Doc () happyRules :: ModuleName -> Bool -> [(Cat, Map RHS RuleLabel)] -> Doc () printRule :: ModuleName -> Bool -> Cat -> Map RHS RuleLabel -> Doc () constructRule :: Bool -> ModuleName -> (RHS, RuleLabel) -> Doc () footer :: ModuleName -> [String] -> TokenText -> Bool -> [Cat] -> Doc () module BNFC.Backend.Haskell.Lexer haskellLexer :: LBNF -> State HaskellBackendState Result cf2lexer :: LBNF -> String -> Bool -> Maybe String -> TokenText -> [Token] -> String cf2doc :: LBNF -> String -> Bool -> Maybe String -> TokenText -> [Token] -> Doc () prelude :: String -> Bool -> Maybe String -> TokenText -> Doc () -- | Character class definitions. cMacros :: Doc () -- | Regular expressions and lex actions. rMacros :: LBNF -> Doc () restOfAlex :: TokenText -> [Token] -> LBNF -> Doc () printRegAlex :: Regex -> Doc () class Print a prt :: Print a => Int -> a -> Doc () instance BNFC.Backend.Haskell.Lexer.Print a => BNFC.Backend.Haskell.Lexer.Print [a] instance BNFC.Backend.Haskell.Lexer.Print GHC.Types.Char instance BNFC.Backend.Haskell.Lexer.Print BNFC.Types.Regex.Regex instance BNFC.Backend.Haskell.Lexer.Print BNFC.Types.Regex.CharClassUnion instance BNFC.Backend.Haskell.Lexer.Print BNFC.Types.Regex.CharClassAtom 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 -> Doc () module BNFC.Backend.Haskell.Makefile haskellmakefile :: LBNF -> State HaskellBackendState Result cf2makefile :: LBNF -> HaskellBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> String makefileDoc :: LBNF -> HaskellBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> Doc () module BNFC.Backend.Haskell instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetHaskell module BNFC.Backend.CPP data CppBackendOptions CppOpts :: Bool -> Maybe String -> CppBackendOptions [lineNumbers] :: CppBackendOptions -> Bool [nameSpace] :: CppBackendOptions -> Maybe String cppOptionsParser :: Parser CppBackendOptions data CppBackendState instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetCpp module BNFC.Backend.C newtype CBackendOptions COpts :: Bool -> CBackendOptions cOptionsParser :: Parser CBackendOptions data CBackendState instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetC module BNFC.Backend.Agda.Utilities.Utils -- | Import the builtin numeric types (content of some token categories)? data ImportNumeric -- | Import the numeric types. YesImportNumeric :: ImportNumeric -- | Don't import the numeric types. NoImportNumeric :: ImportNumeric imports :: ImportNumeric -> Bool -> Bool -> Bool -> Doc () importPragmas :: Bool -> [ModuleName] -> Doc () sanitize :: String -> String -- | How to print the types of constructors in Agda? data ConstructorStyle -- | Simply typed, like E → S → S → S. UnnamedArg :: ConstructorStyle -- | Dependently typed, like (e : E) (s₁ s₂ : S) → S. NamedArg :: ConstructorStyle -- | Suggest the name of a bound variable of the given category. -- --
-- >>> map nameSuggestion -- [ ListType (BaseType (BaseCat 'S':|"tm")), BaseType (TokenCat 'V':|"ar"), (BaseType (BaseCat 'E':|"xp") ] -- ["ss","x","e"] --nameSuggestion :: Type -> String -- | Suggest the name of a bound variable of the given base category. -- --
-- >>> map nameFor ["Stm","ABC","#String"] -- ["s","a","s"] --nameFor :: String1 -> String -- | Number duplicate elements in a list consecutively, starting with 1. -- --
-- >>> numberUniquely ["a", "b", "a", "a", "c", "b"] -- [(Just 1,"a"),(Just 1,"b"),(Just 2,"a"),(Just 3,"a"),(Nothing,"c"),(Just 2,"b")] --numberUniquely :: forall a. Ord a => [a] -> [(Maybe Int, a)] -- | A frequency map. -- -- NB: this type synonym should be local to numberUniquely, but -- Haskell lacks local type synonyms. -- https://gitlab.haskell.org/ghc/ghc/issues/4020 type Frequency a = Map a Int -- | Increase the frequency of the given key. incr :: Ord a => a -> Frequency a -> Frequency a uArrow :: String instance GHC.Classes.Eq BNFC.Backend.Agda.Utilities.Utils.ImportNumeric module BNFC.Backend.Agda.Utilities.ReservedWords -- | A list of Agda keywords that would clash with generated names. agdaReservedWords :: [String] -- | Turn identifier to non-capital identifier. Needed, since in Agda a -- constructor cannot overload a data type with the same name. -- --
-- >>> map agdaLower ["SFun","foo","ABC","HelloWorld","module","Type_int","C1"] -- ["sFun","foo","aBC","helloWorld","module'","type-int","c1"] --agdaLower :: String1 -> String1 -- | Avoid Agda reserved words. avoidAgdaReservedWords :: String1 -> String1 -- | Apply agdaLower function to AST rhs types. avoidResWordsASTRulesAgda :: [(Type, [(Label, [Type])])] -> [(Type, [(Label, [Type])])] lowerLabel :: Label -> Label avoidResWordsType :: Type -> Type avoidResWordsCat :: Cat -> Cat avoidResWordsBaseCat :: BaseCat -> BaseCat processFunctionsAgda :: [(LabelName, Function)] -> [(LabelName, Function)] checkFun :: Function -> Function checkPars :: [Parameter] -> [Parameter] checkPar :: Parameter -> Parameter checkBody :: Exp -> Exp module BNFC.Backend.Agda.Options data AgdaBackendOptions AgdaOpts :: Maybe String -> Bool -> Bool -> Bool -> AgdaBackendOptions [nameSpace] :: AgdaBackendOptions -> Maybe String [inDir] :: AgdaBackendOptions -> Bool [functor] :: AgdaBackendOptions -> Bool [generic] :: AgdaBackendOptions -> Bool agdaOptionsParser :: Parser AgdaBackendOptions printAgdaOptions :: AgdaBackendOptions -> String -- | Commands Subparsers. module BNFC.Options.Commands -- | subcommands parser. commandsParser :: Parser Command data Command Agda :: AgdaBackendOptions -> Command C :: CBackendOptions -> Command Cpp :: CppBackendOptions -> Command Haskell :: HaskellBackendOptions -> Command Java :: JavaBackendOptions -> Command Latex :: LatexBackendOptions -> Command OCaml :: OcamlBackendOptions -> Command Txt2Tags :: Txt2TagsBackendOptions -> Command Check :: Command module BNFC.Backend.Agda.State data AgdaBackendState AgdaSt :: GlobalOptions -> AgdaBackendOptions -> [Token] -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(Type, [(Label, [Type])])] -> [(Cat, Map RHS RuleLabel)] -> [(LabelName, Function)] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> AgdaBackendState [globalOpt] :: AgdaBackendState -> GlobalOptions [agdaOpts] :: AgdaBackendState -> AgdaBackendOptions [lexerParserTokens] :: AgdaBackendState -> [Token] [hsAstRules] :: AgdaBackendState -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] [agdaAstRules] :: AgdaBackendState -> [(Type, [(Label, [Type])])] [parserRules] :: AgdaBackendState -> [(Cat, Map RHS RuleLabel)] [hsFunctions] :: AgdaBackendState -> [(LabelName, Function)] [agdaFunctions] :: AgdaBackendState -> [(LabelName, Function)] [tokens] :: AgdaBackendState -> [(CatName, TokenDef)] module BNFC.Backend.Agda.Test agdaParserTest :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.Template agdaTemplate :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.Printer agdaPrinter :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.Parser agdaParser :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.Makefile agdaMakefile :: LBNF -> State AgdaBackendState Result cf2makefile :: LBNF -> AgdaBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> String makefileDoc :: LBNF -> AgdaBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> Doc () module BNFC.Backend.Agda.Main agdaMain :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.Lexer agdaLexer :: LBNF -> State AgdaBackendState Result module BNFC.Backend.Agda.InitState agdaInitState :: LBNF -> GlobalOptions -> AgdaBackendOptions -> Except String AgdaBackendState processASTRulesAgda :: [String] -> [(Type, [(Label, ([Type], (Integer, ARHS)))])] -> [(Type, [(Label, [Type])])] toAgdaRules :: (Type, [(Label, ([Type], (Integer, ARHS)))]) -> (Type, [(Label, [Type])]) filterRules :: [String] -> [(Type, [(Label, [Type])])] -> [(Type, [(Label, [Type])])] -- | Filter Labels that will be printed in the Agda AST datatypes. filterLabelsAgdaAST :: [String] -> [(Label, [Type])] -> [(Label, [Type])] module BNFC.Backend.Agda.IOLib agdaIOLib :: State AgdaBackendState Result module BNFC.Backend.Agda.AbstractSyntax agdaAbstractSyntax :: LBNF -> State AgdaBackendState Result cf2AST :: LBNF -> String -> Bool -> Maybe String -> [(Type, [(Label, [Type])])] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> [CatName] -> Bool -> String cf2doc :: LBNF -> String -> Bool -> Maybe String -> [(Type, [(Label, [Type])])] -> [(LabelName, Function)] -> [(CatName, TokenDef)] -> [CatName] -> Bool -> Doc () -- | Print Agda types for user defined tokens. prTokens :: ModuleName -> [(CatName, TokenDef)] -> Doc () prToken :: ModuleName -> (CatName, TokenDef) -> Doc () -- | Print Agda types for categories in AST rules. prDatas :: Bool -> ModuleName -> ConstructorStyle -> [(Type, [(Label, [Type])])] -> Doc () -- | Pretty-print Agda data types and pragmas for AST. prData :: Bool -> ModuleName -> ConstructorStyle -> (Type, [(Label, [Type])]) -> Doc () -- | Pretty-print Agda data types and pragmas. prData' :: ModuleName -> ConstructorStyle -> Doc () -> Doc () -> [(Label, [Type])] -> Doc () -- | Pretty-print AST definition in Agda syntax. prettyData :: ConstructorStyle -> Doc () -> [(Label, [Type])] -> Doc () printCase :: ConstructorStyle -> Doc () -> (Label, [Type]) -> Doc () printConstructorArgs :: ConstructorStyle -> [Type] -> Doc () prettyType :: Type -> String compilePragma :: ModuleName -> Doc () -> Doc () -> [Doc ()] -> Doc () -- | Generate Haskell/Agda code for the defined constructors. prFunctions :: Bool -> [(LabelName, Function)] -> Doc () prFunction :: Bool -> (LabelName, Function) -> Doc () printerBindings :: ModuleName -> [Type] -> [BuiltinCat] -> [CatName] -> Doc () prPrinterBindings :: [(Doc (), Doc ())] -> Doc () prPrinterBinding :: (Doc (), Doc ()) -> Doc () prPrinterPragmas :: [(Doc (), (Doc (), Doc ()))] -> Doc () prPrinterPragma :: (Doc (), (Doc (), Doc ())) -> Doc () module BNFC.Backend.Agda instance BNFC.Backend.CommonInterface.Backend.Backend 'BNFC.Options.Target.TargetAgda module Paths_BNFC3 version :: Version getBinDir :: IO FilePath getLibDir :: IO FilePath getDynLibDir :: IO FilePath getDataDir :: IO FilePath getLibexecDir :: IO FilePath getDataFileName :: FilePath -> IO FilePath getSysconfDir :: IO FilePath module BNFC.Options.Version -- | The program version obtained from the cabal file. version :: String -- | Info options. module BNFC.Options.InfoOptions self :: String versionOption :: Parser (a -> a) versionWords :: [String] numericVersionOption :: Parser (a -> a) licenseOption :: Parser (a -> a) module BNFC.Options data Options Options :: GlobalOptions -> Command -> Options [globalOptions] :: Options -> GlobalOptions [command] :: Options -> Command programOptions :: Parser Options getOptInput :: Options -> FilePath options :: IO Options options' :: [String] -> IO Options type Target = Maybe FilePath -- | Like execParser, but parse given argument list rather than -- those from getArgs. execParser' :: [String] -> ParserInfo a -> IO a -- | Run a program description with custom preferences. customExecParser' :: ParserPrefs -> [String] -> ParserInfo a -> IO a module BNFC.Main type Err = Either String -- | BNFC main. bnfc :: IO () -- | Entrypoint with argument vector. bnfcArgs :: [String] -> IO () -- | Entrypoint with parsed options. bnfcOptions :: Options -> IO () -- | Entrypoint with parsed options and parsed grammar. bnfcGrammar :: Options -> Grammar -> IO () type Msgs = [String] execRun :: ((Maybe Result, Maybe FilePath), Msgs) -> IO () -- | Entrypoint with argument vector. runBnfcArgs :: [String] -> IO ((Maybe Result, Maybe FilePath), Msgs) -- | Entrypoint with parsed options. runBnfcOptions :: Options -> IO ((Maybe Result, Maybe FilePath), Msgs) -- | Entrypoint with parsed options and grammar. runBnfcGrammar :: Options -> Grammar -> ((Maybe Result, Maybe FilePath), Msgs) -- | Write to files. writeResult :: Maybe FilePath -> Result -> IO () getAbs :: LBNF -> String parseFile :: FilePath -> IO Grammar dieIfError :: Err a -> IO a