Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides combinators for constructing Haskell declarations.
Synopsis
- type HsBind' = HsBind GhcPs
- class HasValBind t
- typeSig :: HasValBind t => OccNameStr -> HsType' -> t
- typeSigs :: HasValBind t => [OccNameStr] -> HsType' -> t
- funBind :: HasValBind t => OccNameStr -> RawMatch -> t
- funBinds :: HasValBind t => OccNameStr -> [RawMatch] -> t
- funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawMatch] -> t
- valBind :: HasValBind t => OccNameStr -> HsExpr' -> t
- valBindGRHSs :: HasValBind t => OccNameStr -> RawGRHSs -> t
- class HasValBind t => HasPatBind t
- patBind :: HasPatBind t => Pat' -> HsExpr' -> t
- patBindGRHSs :: HasPatBind t => Pat' -> RawGRHSs -> t
- data RawMatch
- match :: [Pat'] -> HsExpr' -> RawMatch
- matchGRHSs :: [Pat'] -> RawGRHSs -> RawMatch
- data RawGRHSs
- rhs :: HsExpr' -> RawGRHSs
- guardedRhs :: [GuardedExpr] -> RawGRHSs
- type GuardedExpr = GRHS' LHsExpr'
- type GRHS' = GRHS GhcPs
- guards :: [Stmt'] -> HsExpr' -> GuardedExpr
- guard :: HsExpr' -> HsExpr' -> GuardedExpr
- where' :: RawGRHSs -> [RawValBind] -> RawGRHSs
- data RawValBind
- stmt :: HsExpr' -> Stmt'
- (<--) :: Pat' -> HsExpr' -> Stmt'
Bindings
class HasValBind t Source #
Syntax types which can declare/define functions. For example: declarations, or the body of a class declaration or class instance.
To declare the type of a function or value, use
typeSig
or typeSigs
.
To define a function, use
funBind
or funBinds
.
To define a value, use
valBind
or valBindGuarded
.
sigB, bindB
Instances
HasValBind HsDecl' Source # | |
HasValBind RawValBind Source # | |
Defined in GHC.SourceGen.Binds.Internal sigB :: Sig' -> RawValBind bindB :: HsBind' -> RawValBind | |
HasValBind RawInstDecl Source # | |
Defined in GHC.SourceGen.Decl sigB :: Sig' -> RawInstDecl bindB :: HsBind' -> RawInstDecl | |
HasValBind ClassDecl Source # | |
Type signatures
typeSig :: HasValBind t => OccNameStr -> HsType' -> t Source #
Declares the type of a single function or value.
f :: A ===== typeSig "f" (var "A")
typeSigs :: HasValBind t => [OccNameStr] -> HsType' -> t Source #
Declares the type of multiple functions or values.
f, g :: A ===== typeSigs ["f", "g"] (var "A")
Functions
funBind :: HasValBind t => OccNameStr -> RawMatch -> t Source #
Defines a function that has a single case.
f = x ===== funBind "f" (match [] "x")
id x = x ===== funBind "id" $ match [bvar "x"] (var "x")
funBinds :: HasValBind t => OccNameStr -> [RawMatch] -> t Source #
Defines a function or value.
f = x ===== funBinds "f" [match [] "x"]
id x = x ===== funBinds "id" [match [var "x"] (var "x")]
not True = False not False = True ===== funBinds "not" [ match [conP "True" []] (var "False") , match [conP "False" []] (var "True") ]
funBindsWithFixity :: HasValBind t => Maybe LexicalFixity -> OccNameStr -> [RawMatch] -> t Source #
Defines a function or value, with an explicit fixity. When given
Nothing
, use infix notation iff the given name is symbolic.
id x = x ===== funBindsWithFixity (Just Prefix) "id" [match [var "x"] (var "x")]
True && True = True True && False = False ===== funBindsWithFixity Nothing "not" [ match [conP "True" []] (var "False") , match [conP "False" []] (var "True") ]
Values
valBind :: HasValBind t => OccNameStr -> HsExpr' -> t Source #
Defines a value without any guards.
The resulting syntax is the same as a function with no arguments.
x = y ===== valBind "x" $ var "y"
valBindGRHSs :: HasValBind t => OccNameStr -> RawGRHSs -> t Source #
Defines a value consisting of multiple guards.
The resulting syntax is the same as a function with no arguments.
x | test = 1 | otherwise = 2 ===== valBindGRHSs "x" $ guardedRhs [ var "test" `guard` int 1 , var "otherwise" `guard` int 2 ]
Patterns
class HasValBind t => HasPatBind t Source #
Syntax types which can declare/define pattern bindings. For example: declarations at the top-level or in let/where clauses.
Note: this class is more restrictive than HasValBind
since pattern
bindings cannot be used in class or instance declarations.
Instances
HasPatBind HsDecl' Source # | |
Defined in GHC.SourceGen.Binds | |
HasPatBind RawValBind Source # | |
Defined in GHC.SourceGen.Binds |
patBind :: HasPatBind t => Pat' -> HsExpr' -> t Source #
Defines a pattern binding without any guards.
(x, y) = e ===== patBind (tuple [bvar "x", bvar "y"]) e
patBindGRHSs :: HasPatBind t => Pat' -> RawGRHSs -> t Source #
Defines a pattern binding consisting of multiple guards.
(x, y) | test = (1, 2) | otherwise = (2, 3) ===== patBindGrhs (tuple [bvar "x", bvar "y"]) $ guardedRhs [ var "test" `guard` tuple [int 1, int 2] , var "otherwise" `guard` [int 2, int 3] ]
Matches
A function definition is made up of one or more RawMatch
terms. Each
RawMatch
corresponds to a single pattern match. For example, to define the
"not" function:
not True = False not False = True
We could using a list of two RawMatch
es:
funBinds "not" [ match [conP "True" []] (var "False") , match [conP "False" [] (var "True") ]
A match may consist of one or more guarded expressions. For example, to define the function as:
not x | x = False | otherwise = True
We would say:
funBind "not" $ matchGRHSs [bvar "x"] $ guardedRhs [ guard (var "x") (var "False") , guard (var "otherwise") (var "True") ]
A single function pattern match, including an optional "where" clause.
For example:
f x | cond = y | otherwise = z where y = ... z = ...
matchGRHSs :: [Pat'] -> RawGRHSs -> RawMatch Source #
A function match consisting of multiple guards.
Right-hand sides
A set of match guards plus an optional "where" clause.
This type is used in matches and in multi-way if expressions.
For example:
| cond = y | otherwise = z where y = ... z = ...
Guards
guardedRhs :: [GuardedExpr] -> RawGRHSs Source #
A guarded right-hand side of a match.
| x = False | otherwise = True ===== guardedRhs [ guard (var "x") (var "False") , guard (var "otherwise") (var "True") ]
type GuardedExpr = GRHS' LHsExpr' Source #
An expression with a single guard.
For example:
| otherwise = ()
guards :: [Stmt'] -> HsExpr' -> GuardedExpr Source #
An expression guarded by multiple statements, using the PatternGuards
extension.
| Just y <- x, y = () ===== guards [conP "Just" (bvar "x") <-- var "y", bvar "x"] unit
guard :: HsExpr' -> HsExpr' -> GuardedExpr Source #
An expression guarded by a single boolean statement.
| otherwise = () ===== guard (var "otherwise") unit
Where clauses
where' :: RawGRHSs -> [RawValBind] -> RawGRHSs Source #
Adds a "where" clause to an existing RawGRHSs
.
f x = y where y = x ===== funBind "x" $ matchGRHSs [bvar "x"] $ rhs (var "y") `where` [valBind "y" $ var "x']
data RawValBind Source #
A binding definition inside of a let
or where
clause.
RawValBind
definitions may be constructed using its instance of
HasValBind
. For more details, see the documentation of that function, and
of GHC.SourceGen.Binds overall.
Instances
HasValBind RawValBind Source # | |
Defined in GHC.SourceGen.Binds.Internal sigB :: Sig' -> RawValBind bindB :: HsBind' -> RawValBind | |
HasPatBind RawValBind Source # | |
Defined in GHC.SourceGen.Binds |