| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.Tools.AST.Binds
Contents
Description
Representation of Haskell AST value and function bindings (both local and top-level)
- data ValueBind dom stage
- = SimpleBind {
- _valBindPat :: Ann Pattern dom stage
- _valBindRhs :: Ann Rhs dom stage
- _valBindLocals :: AnnMaybe LocalBinds dom stage
- | FunBind {
- _funBindMatches :: AnnList Match dom stage
- = SimpleBind {
- data Match dom stage = Match {
- _matchLhs :: Ann MatchLhs dom stage
- _matchRhs :: Ann Rhs dom stage
- _matchBinds :: AnnMaybe LocalBinds dom stage
- data MatchLhs dom stage
- = NormalLhs {
- _matchLhsName :: Ann Name dom stage
- _matchLhsArgs :: AnnList Pattern dom stage
- | InfixLhs {
- _matchLhsLhs :: Ann Pattern dom stage
- _matchLhsOperator :: Ann Operator dom stage
- _matchLhsRhs :: Ann Pattern dom stage
- _matchLhsArgs :: AnnList Pattern dom stage
- = NormalLhs {
- data LocalBinds dom stage = LocalBinds {
- _localBinds :: AnnList LocalBind dom stage
- data LocalBind dom stage
- = LocalValBind { }
- | LocalSignature {
- _localSig :: Ann TypeSignature dom stage
- | LocalFixity {
- _localFixity :: Ann FixitySignature dom stage
- data TypeSignature dom stage = TypeSignature {}
- data FixitySignature dom stage = FixitySignature {
- _fixityAssoc :: Ann Assoc dom stage
- _fixityPrecedence :: Ann Precedence dom stage
- _fixityOperators :: AnnList Operator dom stage
- data Rhs dom stage
- = UnguardedRhs { }
- | GuardedRhss {
- _rhsGuards :: AnnList GuardedRhs dom stage
- data GuardedRhs dom stage = GuardedRhs {
- _guardStmts :: AnnList RhsGuard dom stage
- _guardExpr :: Ann Expr dom stage
- data RhsGuard dom stage
- = GuardBind { }
- | GuardLet {
- _guardBinds :: AnnList LocalBind dom stage
- | GuardCheck {
- _guardCheck :: Ann Expr dom stage
- data TopLevelPragma dom stage
- = RulePragma {
- _pragmaRule :: AnnList Rule dom stage
- | DeprPragma {
- _pragmaObjects :: AnnList Name dom stage
- _pragmaMessage :: Ann StringNode dom stage
- | WarningPragma {
- _pragmaObjects :: AnnList Name dom stage
- _pragmaMessage :: Ann StringNode dom stage
- | AnnPragma {
- _annotationSubject :: Ann AnnotationSubject dom stage
- _annotateExpr :: Ann Expr dom stage
- | InlinePragma {
- _pragmaConlike :: AnnMaybe ConlikeAnnot dom stage
- _pragmaPhase :: AnnMaybe PhaseControl dom stage
- _inlineDef :: Ann Name dom stage
- | NoInlinePragma {
- _pragmaConlike :: AnnMaybe ConlikeAnnot dom stage
- _pragmaPhase :: AnnMaybe PhaseControl dom stage
- _noInlineDef :: Ann Name dom stage
- | InlinablePragma {
- _pragmaPhase :: AnnMaybe PhaseControl dom stage
- _inlinableDef :: Ann Name dom stage
- | LinePragma {
- _pragmaLineNum :: Ann LineNumber dom stage
- _pragmaFileName :: AnnMaybe StringNode dom stage
- | SpecializePragma {
- _pragmaPhase :: AnnMaybe PhaseControl dom stage
- _specializeDef :: Ann Name dom stage
- _specializeType :: AnnList Type dom stage
- = RulePragma {
- data Rule dom stage = Rule {
- _ruleName :: Ann StringNode dom stage
- _rulePhase :: AnnMaybe PhaseControl dom stage
- _ruleBounded :: AnnList TyVar dom stage
- _ruleLhs :: Ann Expr dom stage
- _ruleRhs :: Ann Expr dom stage
- data AnnotationSubject dom stage
- = NameAnnotation {
- _annotateName :: Ann Name dom stage
- | TypeAnnotation {
- _annotateName :: Ann Name dom stage
- | ModuleAnnotation
- = NameAnnotation {
- data MinimalFormula dom stage
- = MinimalName {
- _minimalName :: Ann Name dom stage
- | MinimalParen {
- _minimalInner :: Ann MinimalFormula dom stage
- | MinimalOr {
- _minimalOrs :: AnnList MinimalFormula dom stage
- | MinimalAnd {
- _minimalAnds :: AnnList MinimalFormula dom stage
- = MinimalName {
Documentation
data ValueBind dom stage Source #
Value binding for top-level and local bindings
Constructors
| SimpleBind | Non-function binding ( |
Fields
| |
| FunBind | Function binding ( |
Fields
| |
Clause of function (or value) binding
Constructors
| Match | |
Fields
| |
data MatchLhs dom stage Source #
Something on the left side of the match
Constructors
| NormalLhs | |
Fields
| |
| InfixLhs | |
Fields
| |
data LocalBinds dom stage Source #
Local bindings attached to a declaration ( where x = 42 )
Constructors
| LocalBinds | |
Fields
| |
Instances
| type Rep (LocalBinds dom stage) Source # | |
data LocalBind dom stage Source #
Bindings that are enabled in local blocks (where or let).
Constructors
| LocalValBind | |
| LocalSignature | |
Fields
| |
| LocalFixity | |
Fields
| |
data TypeSignature dom stage Source #
A type signature ( _f :: Int -> Int )
Instances
| type Rep (TypeSignature dom stage) Source # | |
data FixitySignature dom stage Source #
A fixity signature ( infixl 5 +, - ).
Constructors
| FixitySignature | |
Fields
| |
Instances
| type Rep (FixitySignature dom stage) Source # | |
Right hand side of a value binding (possible with guards): ( = 3 or | x == 1 = 3; | otherwise = 4 )
Constructors
| UnguardedRhs | |
| GuardedRhss | |
Fields
| |
data GuardedRhs dom stage Source #
A guarded right-hand side of a value binding ( | x > 3 = 2 )
Constructors
| GuardedRhs | |
Fields
| |
Instances
| type Rep (GuardedRhs dom stage) Source # | |
data RhsGuard dom stage Source #
Guards for value bindings and pattern matches ( Just v x, v 1 )
Constructors
| GuardBind | |
| GuardLet | |
Fields
| |
| GuardCheck | |
Fields
| |
Pragmas
data TopLevelPragma dom stage Source #
Top level pragmas
Constructors
Instances
| type Rep (TopLevelPragma dom stage) Source # | |
A rewrite rule ( "map/map" forall f g xs. map f (map g xs) = map (f.g) xs )
Constructors
| Rule | |
Fields
| |
data AnnotationSubject dom stage Source #
Annotation allows you to connect an expression to any declaration.
Constructors
| NameAnnotation | The definition with the given name is annotated |
Fields
| |
| TypeAnnotation | A type with the given name is annotated |
Fields
| |
| ModuleAnnotation | The whole module is annotated |
Instances
| type Rep (AnnotationSubject dom stage) Source # | |
data MinimalFormula dom stage Source #
Formulas of minimal annotations declaring which functions should be defined.
Constructors
| MinimalName | |
Fields
| |
| MinimalParen | |
Fields
| |
| MinimalOr | One of the minimal formulas are needed ( |
Fields
| |
| MinimalAnd | Both of the minimal formulas are needed ( |
Fields
| |
Instances
| type Rep (MinimalFormula dom stage) Source # | |