pinchot-0.20.0.0: Write grammars, not parsers

Safe HaskellNone
LanguageHaskell2010

Pinchot.Types

Synopsis

Documentation

type RuleName = String Source #

Type synonym for the name of a production rule. This will be the name of the type constructor for the corresponding type that will be created, so this must be a valid Haskell type constructor name. Typically each context-free grammar that you write will have several production rules; you will want to make sure that every RuleName that you create for a single context-free grammar is unique. However, Pinchot currently does not check for uniqueness. If you use names that are not unique, GHC will give an error message when you try to splice the resulting code, as the data types will not have unique names.

type BranchName = String Source #

Type synonym the the name of an alternative in a nonTerminal. This name must not conflict with any other data constructor in your grammar.

data Rule t Source #

A single production rule.

Instances

Eq t => Eq (Rule t) Source # 

Methods

(==) :: Rule t -> Rule t -> Bool #

(/=) :: Rule t -> Rule t -> Bool #

Data t => Data (Rule t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rule t -> c (Rule t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rule t) #

toConstr :: Rule t -> Constr #

dataTypeOf :: Rule t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Rule t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rule t)) #

gmapT :: (forall b. Data b => b -> b) -> Rule t -> Rule t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rule t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule t -> m (Rule t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule t -> m (Rule t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule t -> m (Rule t) #

Ord t => Ord (Rule t) Source # 

Methods

compare :: Rule t -> Rule t -> Ordering #

(<) :: Rule t -> Rule t -> Bool #

(<=) :: Rule t -> Rule t -> Bool #

(>) :: Rule t -> Rule t -> Bool #

(>=) :: Rule t -> Rule t -> Bool #

max :: Rule t -> Rule t -> Rule t #

min :: Rule t -> Rule t -> Rule t #

Show t => Show (Rule t) Source # 

Methods

showsPrec :: Int -> Rule t -> ShowS #

show :: Rule t -> String #

showList :: [Rule t] -> ShowS #

Generic (Rule t) Source # 

Associated Types

type Rep (Rule t) :: * -> * #

Methods

from :: Rule t -> Rep (Rule t) x #

to :: Rep (Rule t) x -> Rule t #

PrettyVal t => PrettyVal (Rule t) Source # 

Methods

prettyVal :: Rule t -> Value #

listValue :: [Rule t] -> Value

type Rep (Rule t) Source # 
type Rep (Rule t) = D1 (MetaData "Rule" "Pinchot.Types" "pinchot-0.20.0.0-JQ7eu6VnfW8FMCw85vZ8Zl" False) (C1 (MetaCons "Rule" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ruleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RuleName)) ((:*:) (S1 (MetaSel (Just Symbol "_ruleDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "_ruleType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RuleType t))))))

data Branch t Source #

A branch in a sum rule. In Branch s ls, s is the name of the data constructor, and ls is the list of rules that this branch produces.

Constructors

Branch 

Instances

Eq t => Eq (Branch t) Source # 

Methods

(==) :: Branch t -> Branch t -> Bool #

(/=) :: Branch t -> Branch t -> Bool #

Data t => Data (Branch t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Branch t -> c (Branch t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Branch t) #

toConstr :: Branch t -> Constr #

dataTypeOf :: Branch t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Branch t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Branch t)) #

gmapT :: (forall b. Data b => b -> b) -> Branch t -> Branch t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Branch t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Branch t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Branch t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Branch t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Branch t -> m (Branch t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Branch t -> m (Branch t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Branch t -> m (Branch t) #

Ord t => Ord (Branch t) Source # 

Methods

compare :: Branch t -> Branch t -> Ordering #

(<) :: Branch t -> Branch t -> Bool #

(<=) :: Branch t -> Branch t -> Bool #

(>) :: Branch t -> Branch t -> Bool #

(>=) :: Branch t -> Branch t -> Bool #

max :: Branch t -> Branch t -> Branch t #

min :: Branch t -> Branch t -> Branch t #

Show t => Show (Branch t) Source # 

Methods

showsPrec :: Int -> Branch t -> ShowS #

show :: Branch t -> String #

showList :: [Branch t] -> ShowS #

PrettyVal t => PrettyVal (Branch t) Source # 

Methods

prettyVal :: Branch t -> Value #

listValue :: [Branch t] -> Value

data RuleType t Source #

The type of a particular rule.

Constructors

Terminal (Intervals t) 
NonTerminal (NonEmptySeq (Branch t)) 
Wrap (Rule t) 
Record (Seq (Rule t)) 
Opt (Rule t) 
Star (Rule t) 
Plus (Rule t) 

Instances

Eq t => Eq (RuleType t) Source # 

Methods

(==) :: RuleType t -> RuleType t -> Bool #

(/=) :: RuleType t -> RuleType t -> Bool #

Data t => Data (RuleType t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleType t -> c (RuleType t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleType t) #

toConstr :: RuleType t -> Constr #

dataTypeOf :: RuleType t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RuleType t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleType t)) #

gmapT :: (forall b. Data b => b -> b) -> RuleType t -> RuleType t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleType t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleType t -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleType t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleType t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleType t -> m (RuleType t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleType t -> m (RuleType t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleType t -> m (RuleType t) #

Ord t => Ord (RuleType t) Source # 

Methods

compare :: RuleType t -> RuleType t -> Ordering #

(<) :: RuleType t -> RuleType t -> Bool #

(<=) :: RuleType t -> RuleType t -> Bool #

(>) :: RuleType t -> RuleType t -> Bool #

(>=) :: RuleType t -> RuleType t -> Bool #

max :: RuleType t -> RuleType t -> RuleType t #

min :: RuleType t -> RuleType t -> RuleType t #

Show t => Show (RuleType t) Source # 

Methods

showsPrec :: Int -> RuleType t -> ShowS #

show :: RuleType t -> String #

showList :: [RuleType t] -> ShowS #

PrettyVal t => PrettyVal (RuleType t) Source # 

Methods

prettyVal :: RuleType t -> Value #

listValue :: [RuleType t] -> Value

recordFieldName Source #

Arguments

:: Int

Index

-> String

Parent type name

-> String

Inner type name

-> String 

The name of a field in a record, without the leading underscore.

type Qualifier = String Source #

Many functions take an argument that holds the name qualifier for the module that contains the data types created by applying a function such as syntaxTrees or earleyProduct.

You will have to make sure that these data types are in scope. The spliced Template Haskell code has to know where to look for these data types. If you did an unqualified import or if the types are in the same module as the function that takes a Qualifier argument, just pass the empty string here. If you did a qualified import, use the appropriate qualifier here.

For example, if you used import qualified MyAst, pass "MyAst" here. If you used import qualified Data.MyLibrary.MyAst as MyLibrary.MyAst, pass "MyLibrary.MyAst" here.

I recommend that you always create a new module and that all you do in that module is apply syntaxTrees or earleyProduct, and that you then perform an import qualified to bring those names into scope in the module in which you use a function that takes a Qualifier argument. This avoids unlikely, but possible, issues that could otherwise arise due to naming conflicts.

quald Source #

Arguments

:: Qualifier 
-> String

Item to be named - constructor, value, etc.

-> Name 

Prepends a qualifier to a string, and returns the resulting Name.

data Loc Source #

A location.

Constructors

Loc 

Fields

Instances

Eq Loc Source # 

Methods

(==) :: Loc -> Loc -> Bool #

(/=) :: Loc -> Loc -> Bool #

Data Loc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc #

toConstr :: Loc -> Constr #

dataTypeOf :: Loc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Loc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) #

gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r #

gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc #

Ord Loc Source # 

Methods

compare :: Loc -> Loc -> Ordering #

(<) :: Loc -> Loc -> Bool #

(<=) :: Loc -> Loc -> Bool #

(>) :: Loc -> Loc -> Bool #

(>=) :: Loc -> Loc -> Bool #

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Read Loc Source # 
Show Loc Source # 

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Generic Loc Source # 

Associated Types

type Rep Loc :: * -> * #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

PrettyVal Loc Source # 

Methods

prettyVal :: Loc -> Value #

listValue :: [Loc] -> Value

type Rep Loc Source #