pinchot-0.24.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

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.24.0.0-FNVmzC3fiVb8ilWRaT4srD" 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

Show t => Show (Branch t) Source # 

Methods

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

show :: Branch t -> String #

showList :: [Branch t] -> ShowS #

Generic (Branch t) Source # 

Associated Types

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

Methods

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

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

PrettyVal t => PrettyVal (Branch t) Source # 

Methods

prettyVal :: Branch t -> Value #

listValue :: [Branch t] -> Value

type Rep (Branch t) Source # 
type Rep (Branch t) = D1 (MetaData "Branch" "Pinchot.Types" "pinchot-0.24.0.0-FNVmzC3fiVb8ilWRaT4srD" False) (C1 (MetaCons "Branch" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_branchName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchName)) (S1 (MetaSel (Just Symbol "_branches") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Rule t]))))

newtype Predicate a Source #

Constructors

Predicate 

Fields

data RuleType t Source #

The type of a particular rule.

Constructors

Terminal (Predicate t) 
NonTerminal (NonEmpty (Branch t)) 
Wrap (Rule t) 
Record [Rule t] 
Opt (Rule t) 
Star (Rule t) 
Plus (Rule t) 
Series (NonEmpty t) 

Instances

Show t => Show (RuleType t) Source # 

Methods

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

show :: RuleType t -> String #

showList :: [RuleType t] -> ShowS #

Generic (RuleType t) Source # 

Associated Types

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

Methods

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

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

PrettyVal t => PrettyVal (RuleType t) Source # 

Methods

prettyVal :: RuleType t -> Value #

listValue :: [RuleType t] -> Value

type Rep (RuleType t) Source # 

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.

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 #