Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides combinators for constructing Haskell declarations.
Synopsis
- type' :: RdrNameStr -> [RdrNameStr] -> HsType' -> HsDecl'
- newtype' :: RdrNameStr -> [RdrNameStr] -> ConDecl' -> HsDecl'
- data' :: RdrNameStr -> [RdrNameStr] -> [ConDecl'] -> HsDecl'
- patBind :: Pat' -> RawGRHSs -> HsDecl'
- prefixCon :: RdrNameStr -> [Field] -> ConDecl'
- infixCon :: Field -> RdrNameStr -> Field -> ConDecl'
- recordCon :: RdrNameStr -> [(RdrNameStr, Field)] -> ConDecl'
- data Field
- field :: HsType' -> Field
- strict :: Field -> Field
- lazy :: Field -> Field
- class' :: [HsType'] -> RdrNameStr -> [RdrNameStr] -> [ClassDecl] -> HsDecl'
- data ClassDecl
- funDep :: [RdrNameStr] -> [RdrNameStr] -> ClassDecl
- instance' :: HsType' -> [RawInstDecl] -> HsDecl'
- data RawInstDecl
Type declarations
type' :: RdrNameStr -> [RdrNameStr] -> HsType' -> HsDecl' Source #
Declares a type synonym.
type A a b = B b a ===== type' "A" ["a", "b"] $ var "B" @@ var "b" @@ var "a"
newtype' :: RdrNameStr -> [RdrNameStr] -> ConDecl' -> HsDecl' Source #
A newtype declaration.
newtype Const a b = Const a ===== newtype' "Const" ["a", "b"] $ conDecl "Const" [var "a"]
data' :: RdrNameStr -> [RdrNameStr] -> [ConDecl'] -> HsDecl' Source #
A data declaration.
data Either a b = Left a | Right b ===== data' "Either" ["a", "b"] [ conDecl "Left" [var "a"] , conDecl "Right" [var "b"] ]
Pattern bindings
patBind :: Pat' -> RawGRHSs -> HsDecl' Source #
A pattern binding.
x = y ===== patBind (var "x") $ rhs $ var "y"
(x, y) = e ===== patBind (tuple [var "x", var "y"]) $ rhs e
(x, y) | test = (1, 2) | otherwise = (2, 3) ===== patBind (tuple [var "x", var "y"]) $ guardedRhs [ var "test" `guard` tuple [int 1, int 2] , var "otherwise" `guard` [int 2, int 3] ]
Data constructors
prefixCon :: RdrNameStr -> [Field] -> ConDecl' Source #
Declares a Haskell-98-style prefix constructor for a data or type declaration.
Foo a Int ===== conDecl "Foo" [field (var "a"), field (var "Int")]
infixCon :: Field -> RdrNameStr -> Field -> ConDecl' Source #
Declares a Haskell-98-style infix constructor for a data or type declaration.
A b :+: C d ===== infixCon (field (var "A" @@ var "b")) ":+:" (field (Var "C" @@ var "d"))
recordCon :: RdrNameStr -> [(RdrNameStr, Field)] -> ConDecl' Source #
Declares Haskell-98-style record constructor for a data or type declaration.
A { x :: B, y :: C } ===== recordCon "A" [("x", var "B"), ("y", var "C")]
An individual argument of a data constructor. Contains a type for the field, and whether the field is strict or lazy.
field :: HsType' -> Field Source #
A field with no explicit strictness annotations.
A b ===== field $ var "A" @@ var "b"
strict :: Field -> Field Source #
Give a field an explicit strictness annotation. Overrides any such previous
annotations (for example, from lazy
).
!(A b) ===== strict $ field $ var "A" @@ var "b"
lazy :: Field -> Field Source #
Give a field an explicit laziness annotation. This feature is useful in combination
with the StrictData
extension. Overrides any such previous
annotations (for example, from strict
).
!(A b) ===== strict $ field $ var "A" @@ var "b"
Class declarations
:: [HsType'] | Context |
-> RdrNameStr | Class name |
-> [RdrNameStr] | Type parameters |
-> [ClassDecl] | Class declarations |
-> HsDecl' |
A class declaration.
class (Real a, Enum a) => Integral a where divMod :: a -> a -> (a, a) div :: a -> a -> a div x y = fst (divMod x y) ===== let a = var "a" in class' [var "Real" @@ a, var "Enum" @@ a] "Integral" ["a"] [ typeSig "divMod" $ a --> a --> tuple [a, a] , typeSig "div" $ a --> a --> a , funBind "div" $ matchRhs [var "x", var "y"] $ var "fst" @@ (var "divMod" @@ var "x" @@ var "y") ]
A definition that can appear in the body of a class
declaration.
funDep :: [RdrNameStr] -> [RdrNameStr] -> ClassDecl Source #
A functional dependency for a class.
| a, b -> c ===== funDep ["a", "b"] ["c"]
class Ident a b | a -> b, b -> a where ident :: a -> b ===== class' [] "Ident" ["a", "b"] [ funDep ["a"] ["b"] , funDep ["b"] ["a"] , typeSig "ident" $ var "a" --> var "b" ]
Instance declarations
instance' :: HsType' -> [RawInstDecl] -> HsDecl' Source #
An instance declaration.
instance Show Bool where show :: Bool -> String -- Requires the InstanceSigs extension show True = "True" show False = "False" ===== instance' (var "Show" @@ var "Bool") [ typeSig "show" $ var "Bool" --> var "String" , funBinds "show" [ matchRhs [var "True"] $ string "True" , matchRhs [var "False"] $ string "False" ] ]
data RawInstDecl Source #
A definition that can appear in the body of an instance
declaration.
Instances
HasValBind RawInstDecl Source # | |
Defined in GHC.SourceGen.Decl sigB :: Sig' -> RawInstDecl Source # bindB :: HsBind' -> RawInstDecl Source # |