Safe Haskell | None |
---|---|
Language | Haskell2010 |
The abstract syntax of language BNFC.
Synopsis
- type Grammar = Grammar' BNFC'Position
- data Grammar' a = Grammar a [Def' a]
- type Def = Def' BNFC'Position
- data Def' a
- = Rule a (Label' a) (Cat' a) (RHS' a)
- | Comment a String
- | Comments a String String
- | Internal a (Label' a) (Cat' a) (RHS' a)
- | Token a Identifier (Reg' a)
- | PosToken a Identifier (Reg' a)
- | Entryp a [Cat' a]
- | Separator a (MinimumSize' a) (Cat' a) String
- | Terminator a (MinimumSize' a) (Cat' a) String
- | Delimiters a (Cat' a) String String (Separation' a) (MinimumSize' a)
- | Coercions a Identifier Integer
- | Rules a Identifier [RHS' a]
- | Function a Identifier [Arg' a] (Exp' a)
- | Layout a [String]
- | LayoutStop a [String]
- | LayoutTop a
- type Item = Item' BNFC'Position
- data Item' a
- type Cat = Cat' BNFC'Position
- data Cat' a
- = ListCat a (Cat' a)
- | IdCat a Identifier
- type Label = Label' BNFC'Position
- data Label' a
- type Arg = Arg' BNFC'Position
- data Arg' a = Arg a Identifier
- type Separation = Separation' BNFC'Position
- data Separation' a
- type Exp = Exp' BNFC'Position
- data Exp' a
- type RHS = RHS' BNFC'Position
- data RHS' a = RHS a [Item' a]
- type MinimumSize = MinimumSize' BNFC'Position
- data MinimumSize' a
- type Reg = Reg' BNFC'Position
- data Reg' a
- newtype Identifier = Identifier ((Int, Int), String)
- type BNFC'Position = Maybe (Int, Int)
- pattern BNFC'NoPosition :: BNFC'Position
- pattern BNFC'Position :: Int -> Int -> BNFC'Position
- class HasPosition a where
- hasPosition :: a -> BNFC'Position
Documentation
type Grammar = Grammar' BNFC'Position Source #
Instances
type Def = Def' BNFC'Position Source #
Rule a (Label' a) (Cat' a) (RHS' a) | |
Comment a String | |
Comments a String String | |
Internal a (Label' a) (Cat' a) (RHS' a) | |
Token a Identifier (Reg' a) | |
PosToken a Identifier (Reg' a) | |
Entryp a [Cat' a] | |
Separator a (MinimumSize' a) (Cat' a) String | |
Terminator a (MinimumSize' a) (Cat' a) String | |
Delimiters a (Cat' a) String String (Separation' a) (MinimumSize' a) | |
Coercions a Identifier Integer | |
Rules a Identifier [RHS' a] | |
Function a Identifier [Arg' a] (Exp' a) | |
Layout a [String] | |
LayoutStop a [String] | |
LayoutTop a |
Instances
type Item = Item' BNFC'Position Source #
Instances
type Cat = Cat' BNFC'Position Source #
ListCat a (Cat' a) | |
IdCat a Identifier |
Instances
Functor Cat' Source # | |
Foldable Cat' Source # | |
Defined in BNFC.Abs fold :: Monoid m => Cat' m -> m Source # foldMap :: Monoid m => (a -> m) -> Cat' a -> m Source # foldMap' :: Monoid m => (a -> m) -> Cat' a -> m Source # foldr :: (a -> b -> b) -> b -> Cat' a -> b Source # foldr' :: (a -> b -> b) -> b -> Cat' a -> b Source # foldl :: (b -> a -> b) -> b -> Cat' a -> b Source # foldl' :: (b -> a -> b) -> b -> Cat' a -> b Source # foldr1 :: (a -> a -> a) -> Cat' a -> a Source # foldl1 :: (a -> a -> a) -> Cat' a -> a Source # toList :: Cat' a -> [a] Source # null :: Cat' a -> Bool Source # length :: Cat' a -> Int Source # elem :: Eq a => a -> Cat' a -> Bool Source # maximum :: Ord a => Cat' a -> a Source # minimum :: Ord a => Cat' a -> a Source # | |
Traversable Cat' Source # | |
HasPosition Cat Source # | |
Defined in BNFC.Abs hasPosition :: Cat -> BNFC'Position Source # | |
AddCategories Cat Source # | Also adds for each list category its element category, transitively. |
Defined in BNFC.Check.Pass1 | |
Eq a => Eq (Cat' a) Source # | |
Ord a => Ord (Cat' a) Source # | |
Defined in BNFC.Abs | |
Read a => Read (Cat' a) Source # | |
Show a => Show (Cat' a) Source # | |
Print [Cat' a] Source # | |
Print (Cat' a) Source # | |
type Label = Label' BNFC'Position Source #
Instances
type Arg = Arg' BNFC'Position Source #
Instances
type Separation = Separation' BNFC'Position Source #
data Separation' a Source #
Instances
type Exp = Exp' BNFC'Position Source #
Cons a (Exp' a) (Exp' a) | |
App a Identifier [Exp' a] | |
Var a Identifier | |
LitInteger a Integer | |
LitChar a Char | |
LitString a String | |
LitDouble a Double | |
List a [Exp' a] |
Instances
type RHS = RHS' BNFC'Position Source #
Instances
type MinimumSize = MinimumSize' BNFC'Position Source #
data MinimumSize' a Source #
Instances
type Reg = Reg' BNFC'Position Source #
RAlt a (Reg' a) (Reg' a) | |
RMinus a (Reg' a) (Reg' a) | |
RSeq a (Reg' a) (Reg' a) | |
RStar a (Reg' a) | |
RPlus a (Reg' a) | |
ROpt a (Reg' a) | |
REps a | |
RChar a Char | |
RAlts a String | |
RSeqs a String | |
RDigit a | |
RLetter a | |
RUpper a | |
RLower a | |
RAny a |
Instances
newtype Identifier Source #
Identifier ((Int, Int), String) |
Instances
Eq Identifier Source # | |
Defined in BNFC.Abs (==) :: Identifier -> Identifier -> Bool Source # (/=) :: Identifier -> Identifier -> Bool Source # | |
Ord Identifier Source # | |
Defined in BNFC.Abs compare :: Identifier -> Identifier -> Ordering Source # (<) :: Identifier -> Identifier -> Bool Source # (<=) :: Identifier -> Identifier -> Bool Source # (>) :: Identifier -> Identifier -> Bool Source # (>=) :: Identifier -> Identifier -> Bool Source # max :: Identifier -> Identifier -> Identifier Source # min :: Identifier -> Identifier -> Identifier Source # | |
Read Identifier Source # | |
Show Identifier Source # | |
HasPosition Identifier Source # | |
Defined in BNFC.Abs | |
Print Identifier Source # | |
Defined in BNFC.Print |
pattern BNFC'NoPosition :: BNFC'Position Source #
pattern BNFC'Position :: Int -> Int -> BNFC'Position Source #
class HasPosition a where Source #
Get the start position of something.
hasPosition :: a -> BNFC'Position Source #
Instances
HasPosition Identifier Source # | |
Defined in BNFC.Abs | |
HasPosition Reg Source # | |
Defined in BNFC.Abs hasPosition :: Reg -> BNFC'Position Source # | |
HasPosition MinimumSize Source # | |
Defined in BNFC.Abs | |
HasPosition RHS Source # | |
Defined in BNFC.Abs hasPosition :: RHS -> BNFC'Position Source # | |
HasPosition Exp Source # | |
Defined in BNFC.Abs hasPosition :: Exp -> BNFC'Position Source # | |
HasPosition Separation Source # | |
Defined in BNFC.Abs | |
HasPosition Arg Source # | |
Defined in BNFC.Abs hasPosition :: Arg -> BNFC'Position Source # | |
HasPosition Label Source # | |
Defined in BNFC.Abs hasPosition :: Label -> BNFC'Position Source # | |
HasPosition Cat Source # | |
Defined in BNFC.Abs hasPosition :: Cat -> BNFC'Position Source # | |
HasPosition Item Source # | |
Defined in BNFC.Abs hasPosition :: Item -> BNFC'Position Source # | |
HasPosition Def Source # | |
Defined in BNFC.Abs hasPosition :: Def -> BNFC'Position Source # | |
HasPosition Grammar Source # | |
Defined in BNFC.Abs hasPosition :: Grammar -> BNFC'Position Source # |