Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module overloads some combinators so they can be used in different contexts: for expressions, types and/or patterns.
Synopsis
- class Par e where
- par :: e -> e
- class App e where
- (@@) :: e -> e -> e
- op :: e -> RdrNameStr -> e -> e
- class HasTuple e where
- tuple :: HasTuple e => [e] -> e
- unboxedTuple :: HasTuple e => [e] -> e
- class HasList e where
- class BVar a => Var a where
- var :: RdrNameStr -> a
- class BVar a where
- bvar :: OccNameStr -> a
Documentation
A class for wrapping terms in parentheses.
A class for term application.
These functions may add additional parentheses to the AST. GHC's pretty-printing functions expect those parentheses to already be present, because GHC preserves parentheses when it parses the AST from a source file.
(@@) :: e -> e -> e infixl 2 Source #
Prefix-apply a term:
f x ===== var "f" @@ var "x"
(+) x ===== var "+" @@ var "x"
Also parenthesizes the right-hand side in order to preserve its semantics when pretty-printed, but tries to do so only when necessary:
f x y ===== var "f" @@ var "x" @@ var "y" -- equivalently: (var "f" @@ var "x") @@ var "y"
f (g x) ===== var "f" @@ (var "g" @@ var "x")
f (g x) ===== var "f" @@ par (var "g" @@ par (var "x"))
op :: e -> RdrNameStr -> e -> e Source #
Infix-apply an operator or function.
For example:
x + y ===== op (var "x") "+" (var "y")
Also parenthesizes the right-hand side in order to preserve its semantics when pretty-printed, but tries to do so only when necessary:
f x + g y ===== op (var "f" @@ var "x") "+" (var "g" @@ var "y")
x + (y + z) ===== op (var "x") "+" (op (var "y") "+" (var "z"))
f x `plus` g y ===== op (var "f" @@ var "x") "plus" (var "g" @@ var "y")
unboxedTuple :: HasTuple e => [e] -> e Source #
class HasList e where Source #
An explicit list of terms.
[x, y] ===== list [var "x", var "y"]
NOTE: for types, use either listTy
or promotedListTy
.
The empty list []
.
The list cons constructor (:)
.
class BVar a => Var a where Source #
Terms that can contain references to named things. They may be actual variables,
functions, or constructors. For example,
and var
"a"
are equally valid.
Depending on the context, the former could refer to either a function,
value, type variable, or pattern; and the latter could refer to either a type
constructor or a data constructor,var
"A"
var :: RdrNameStr -> a Source #
Instances
Var IE' Source # | |
Defined in GHC.SourceGen.Overloaded var :: RdrNameStr -> IE' Source # | |
Var HsExpr' Source # | |
Defined in GHC.SourceGen.Overloaded var :: RdrNameStr -> HsExpr' Source # | |
Var HsType' Source # | |
Defined in GHC.SourceGen.Overloaded var :: RdrNameStr -> HsType' Source # |
Terms that can contain references to locally-bound variables.
Depending on the context,
could refer to either a
pattern variable or a type variable.bvar
"a"
bvar :: OccNameStr -> a Source #
Instances
BVar HsTyVarBndr' Source # | |
Defined in GHC.SourceGen.Overloaded bvar :: OccNameStr -> HsTyVarBndr' Source # | |
BVar IE' Source # | |
Defined in GHC.SourceGen.Overloaded bvar :: OccNameStr -> IE' Source # | |
BVar HsExpr' Source # | |
Defined in GHC.SourceGen.Overloaded bvar :: OccNameStr -> HsExpr' Source # | |
BVar Pat' Source # | |
Defined in GHC.SourceGen.Overloaded bvar :: OccNameStr -> Pat' Source # | |
BVar HsType' Source # | |
Defined in GHC.SourceGen.Overloaded bvar :: OccNameStr -> HsType' Source # |