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

Safe HaskellNone
LanguageHaskell2010

GHC.SourceGen.Binds

Contents

Description

This module provides combinators for constructing Haskell declarations.

Synopsis

Overloaded constructors

class HasValBind t where Source #

Syntax types which can declare/define functions. For example: declarations, or the body of a class declaration or class instance.

Use typeSig or typeSigs to declare that functions or values have types, and use funBind to give them definitions.

Methods

sigB :: Sig' -> t Source #

bindB :: HsBind' -> t Source #

typeSig :: HasValBind t => RdrNameStr -> HsType' -> t Source #

Declare that a function or value has a type:

f :: A
=====
typeSig "f" (var "A")

typeSigs :: HasValBind t => [RdrNameStr] -> HsType' -> t Source #

Declare that a multiple functions or values have a type:

f, g :: A
=====
typeSigs ["f", "g"] (var "A")

funBind :: HasValBind t => RdrNameStr -> RawMatch -> t Source #

Defines a function that has a single case.

f = x
=====
funBind "f" (matchRhs [] "x")
id x = x
=====
funBind "id" $ matchRhs [var "x"] (var "x")

funBinds :: HasValBind t => RdrNameStr -> [RawMatch] -> t Source #

Define a function or value.

f = x
=====
funBinds "f" [matchRhs [] "x"]
id x = x
=====
funBinds "id" [matchRhs [var "x"] (var "x")]
not True = False
not False = True
=====
funBinds "not"
  [ matchRhs [conP "True" []] (var "False")
  , matchRhs [conP "False" []] (var "True")
  ]

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 RawMatches:

funBinds "not"
  [ matchRhs [conP "True" []] (var "False")
  , matchRhs [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"
     $ match [var "x"] $ guardedRhs
         [ guard (var "x") (var "False")
         , guard (var "otherwise") (var "True")
         ]

data RawMatch Source #

A single function pattern match, including an optional "where" clause.

For example:

f x
   | cond = y
   | otherwise = z
 where
   y = ...
   z = ...

match :: [Pat'] -> RawGRHSs -> RawMatch Source #

A function match consisting of multiple guards.

matchRhs :: [Pat'] -> HsExpr' -> RawMatch Source #

A function match with a single case.

Right-hand sides

data RawGRHSs Source #

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 = ...

rhs :: HsExpr' -> RawGRHSs Source #

A right-hand side of a match, with no guards.

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' (Located HsExpr') 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" (var "x") <-- var "y", var "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"
  $ match [var "x"]
  $ rhs (var "y")
     `where` [patBind (var "y") $ rhs $ var "x']

Statements

stmt :: HsExpr' -> Stmt' Source #

An expression statement. May be used in a do expression (with do') or in a match (with guard).

TODO: also allow using statements in list comprehensions.

(<--) :: Pat' -> HsExpr' -> Stmt' infixl 1 Source #

A statement that binds a pattern.

x <- act
=====
var "x" <-- var "act"