| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
GHC.SourceGen.Decl
Description
This module provides combinators for constructing Haskell declarations.
Synopsis
- type HsDecl' = HsDecl GhcPs
- type' :: OccNameStr -> [HsTyVarBndr'] -> HsType' -> HsDecl'
- newtype' :: OccNameStr -> [HsTyVarBndr'] -> ConDecl' -> [HsDerivingClause'] -> HsDecl'
- data' :: OccNameStr -> [HsTyVarBndr'] -> [ConDecl'] -> [HsDerivingClause'] -> HsDecl'
- type ConDecl' = ConDecl GhcPs
- prefixCon :: OccNameStr -> [Field] -> ConDecl'
- infixCon :: Field -> OccNameStr -> Field -> ConDecl'
- recordCon :: OccNameStr -> [(OccNameStr, Field)] -> ConDecl'
- data Field
- field :: HsType' -> Field
- strict :: Field -> Field
- lazy :: Field -> Field
- type HsDerivingClause' = HsDerivingClause GhcPs
- deriving' :: [HsType'] -> HsDerivingClause'
- derivingStock :: [HsType'] -> HsDerivingClause'
- derivingAnyclass :: [HsType'] -> HsDerivingClause'
- derivingNewtype :: [HsType'] -> HsDerivingClause'
- derivingVia :: HsType' -> [HsType'] -> HsDerivingClause'
- standaloneDeriving :: HsType' -> HsDecl'
- standaloneDerivingStock :: HsType' -> HsDecl'
- standaloneDerivingNewtype :: HsType' -> HsDecl'
- standaloneDerivingAnyclass :: HsType' -> HsDecl'
- class' :: [HsType'] -> OccNameStr -> [HsTyVarBndr'] -> [ClassDecl] -> HsDecl'
- data ClassDecl
- funDep :: [RdrNameStr] -> [RdrNameStr] -> ClassDecl
- instance' :: HsType' -> [RawInstDecl] -> HsDecl'
- data RawInstDecl
- class HasTyFamInst t where
- tyFamInstD :: TyFamInstDecl' -> t
- tyFamInst :: HasTyFamInst t => RdrNameStr -> [HsType'] -> HsType' -> t
- patSynSigs :: [OccNameStr] -> HsType' -> HsDecl'
- patSynSig :: OccNameStr -> HsType' -> HsDecl'
- patSynBind :: OccNameStr -> [OccNameStr] -> Pat' -> HsDecl'
Documentation
Type declarations
type' :: OccNameStr -> [HsTyVarBndr'] -> HsType' -> HsDecl' Source #
Declares a type synonym.
type A a b = B b a ===== type' "A" [bvar "a", bvar "b"] $ var "B" @@ var "b" @@ var "a"
newtype' :: OccNameStr -> [HsTyVarBndr'] -> ConDecl' -> [HsDerivingClause'] -> HsDecl' Source #
A newtype declaration.
newtype Const a b = Const a deriving Eq ===== newtype' "Const" [bvar "a", bvar "b"] (conDecl "Const" [var "a"]) [var "Show"]
data' :: OccNameStr -> [HsTyVarBndr'] -> [ConDecl'] -> [HsDerivingClause'] -> HsDecl' Source #
A data declaration.
data Either a b = Left a | Right b deriving Show ===== data' "Either" [bvar "a", bvar "b"] [ conDecl "Left" [var "a"] , conDecl "Right" [var "b"] ] [var "Show"]
Data constructors
prefixCon :: OccNameStr -> [Field] -> ConDecl' Source #
Declares a Haskell-98-style prefix constructor for a data or type declaration.
Foo a Int ===== prefixCon "Foo" [field (var "a"), field (var "Int")]
infixCon :: Field -> OccNameStr -> 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 :: OccNameStr -> [(OccNameStr, 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"
Deriving clauses
deriving' :: [HsType'] -> HsDerivingClause' Source #
derivingStock :: [HsType'] -> HsDerivingClause' Source #
derivingAnyclass :: [HsType'] -> HsDerivingClause' Source #
derivingNewtype :: [HsType'] -> HsDerivingClause' Source #
derivingVia :: HsType' -> [HsType'] -> HsDerivingClause' Source #
A DerivingVia clause.
deriving (Eq, Show) via T ===== derivingVia (var "T") [var "Eq", var "Show"]
Available with ghc>=8.6.
standaloneDeriving :: HsType' -> HsDecl' Source #
Class declarations
Arguments
| :: [HsType'] | Context |
| -> OccNameStr | Class name |
| -> [HsTyVarBndr'] | 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"
[bvar "a"]
[ typeSig "divMod" $ a --> a --> tuple [a, a]
, typeSig "div" $ a --> a --> a
, funBind "div"
$ match [bvar "x", bvar "y"]
$ var "fst" @@ (var "divMod" @@ var "x" @@ var "y")
]A definition that can appear in the body of a class declaration.
ClassDecl definitions may be constructed using funDep or using the
instance of HasValBind. For more details, see the documentation of
that function, and of GHC.SourceGen.Binds overall.
Instances
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"
[ match [bvar "True"] $ string "True"
, match [bvar "False"] $ string "False"
]
]data RawInstDecl Source #
A definition that can appear in the body of an instance declaration.
RawInstDecl definitions may be constructed using its class instances, e.g.,
HasValBind. For more details, see the documentation of those classes.
Instances
| HasValBind RawInstDecl Source # | |
Defined in GHC.SourceGen.Decl | |
| HasTyFamInst RawInstDecl Source # | |
Defined in GHC.SourceGen.Decl Methods tyFamInstD :: TyFamInstDecl' -> RawInstDecl Source # | |
class HasTyFamInst t where Source #
Terms which can contain a type instance declaration.
To use this class, call tyFamInst.
Methods
tyFamInstD :: TyFamInstDecl' -> t Source #
Instances
| HasTyFamInst RawInstDecl Source # | |
Defined in GHC.SourceGen.Decl Methods tyFamInstD :: TyFamInstDecl' -> RawInstDecl Source # | |
| HasTyFamInst HsDecl' Source # | |
Defined in GHC.SourceGen.Decl Methods tyFamInstD :: TyFamInstDecl' -> HsDecl' Source # | |
tyFamInst :: HasTyFamInst t => RdrNameStr -> [HsType'] -> HsType' -> t Source #
A type family instance.
type Elt String = Char ===== tyFamInst "Elt" [var "String"] (var "Char")
Pattern synonyms
patSynSigs :: [OccNameStr] -> HsType' -> HsDecl' Source #
Declares multiple pattern signatures of the same type.
pattern F, G :: T ===== patSynSigs ["F", "G"] $ var "T"
patSynSig :: OccNameStr -> HsType' -> HsDecl' Source #
Declares a pattern signature and its type.
pattern F :: T ===== patSynSigs "F" $ var "T"
patSynBind :: OccNameStr -> [OccNameStr] -> Pat' -> HsDecl' Source #
Defines a pattern signature.
pattern F a b = G b a ===== patSynBind "F" ["a", "b"] $ conP "G" [bvar "b", bvar "a"]