ghc-source-gen-0.2.0.1: Constructs Haskell syntax trees for the GHC API.

Safe HaskellNone
LanguageHaskell2010

GHC.SourceGen.Decl

Contents

Description

This module provides combinators for constructing Haskell declarations.

Synopsis

Documentation

type HsDecl' = HsDecl GhcPs Source #

A Haskell declaration, as it is represented after the parsing step.

Instances:

Type declarations

type' :: OccNameStr -> [OccNameStr] -> 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' :: OccNameStr -> [OccNameStr] -> ConDecl' -> [HsDerivingClause'] -> HsDecl' Source #

A newtype declaration.

newtype Const a b = Const a deriving Eq
=====
newtype' "Const" ["a", "b"]
   (conDecl "Const" [var "a"])
   [var "Show"]

data' :: OccNameStr -> [OccNameStr] -> [ConDecl'] -> [HsDerivingClause'] -> HsDecl' Source #

A data declaration.

data Either a b = Left a | Right b
   deriving Show
=====
data' "Either" ["a", "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
=====
conDecl "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")]

data Field Source #

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

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.

Class declarations

class' Source #

Arguments

:: [HsType']

Context

-> OccNameStr

Class name

-> [OccNameStr]

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"
         $ match [bvar "x", bvar "y"]
            $ var "fst" @@ (var "divMod" @@ var "x" @@ var "y")
     ]

data ClassDecl Source #

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
HasValBind ClassDecl Source # 
Instance details

Defined in GHC.SourceGen.Decl

Methods

sigB :: Sig' -> ClassDecl

bindB :: HsBind' -> ClassDecl

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 # 
Instance details

Defined in GHC.SourceGen.Decl

Methods

sigB :: Sig' -> RawInstDecl

bindB :: HsBind' -> RawInstDecl

HasTyFamInst RawInstDecl Source # 
Instance details

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 HsDecl' Source # 
Instance details

Defined in GHC.SourceGen.Decl

Methods

tyFamInstD :: TyFamInstDecl' -> HsDecl' Source #

HasTyFamInst RawInstDecl Source # 
Instance details

Defined in GHC.SourceGen.Decl

Methods

tyFamInstD :: TyFamInstDecl' -> RawInstDecl 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"]