template-haskell-2.11.0.0: Support library for Template Haskell

Copyright(c) The University of Glasgow 2003
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Syntax

Contents

Description

Abstract syntax definitions for Template Haskell.

Synopsis

Documentation

class (Applicative m, Monad m) => Quasi m where Source

Instances

Quasi IO 
Quasi Q 

newtype Q a Source

Constructors

Q 

Fields

Instances

Monad Q 

Methods

(>>=) :: Q a -> (a -> Q b) -> Q b Source

(>>) :: Q a -> Q b -> Q b Source

return :: a -> Q a Source

fail :: String -> Q a Source

Functor Q 

Methods

fmap :: (a -> b) -> Q a -> Q b Source

(<$) :: a -> Q b -> Q a Source

Applicative Q 

Methods

pure :: a -> Q a Source

(<*>) :: Q (a -> b) -> Q a -> Q b Source

(*>) :: Q a -> Q b -> Q b Source

(<*) :: Q a -> Q b -> Q a Source

Quasi Q 

runQ :: Quasi m => Q a -> m a Source

newtype TExp a Source

Constructors

TExp 

Fields

unTypeQ :: Q (TExp a) -> Q Exp Source

newName :: String -> Q Name Source

Generate a fresh name, which cannot be captured.

For example, this:

f = $(do
  nm1 <- newName "x"
  let nm2 = mkName "x"
  return (LamE [VarP nm1] (LamE [VarP nm2] (VarE nm1)))
 )

will produce the splice

f = \x0 -> \x -> x0

In particular, the occurrence VarE nm1 refers to the binding VarP nm1, and is not captured by the binding VarP nm2.

Although names generated by newName cannot be captured, they can capture other names. For example, this:

g = $(do
  nm1 <- newName "x"
  let nm2 = mkName "x"
  return (LamE [VarP nm2] (LamE [VarP nm1] (VarE nm2)))
 )

will produce the splice

g = \x -> \x0 -> x0

since the occurrence VarE nm2 is captured by the innermost binding of x, namely VarP nm1.

report :: Bool -> String -> Q () Source

Deprecated: Use reportError or reportWarning instead

Report an error (True) or warning (False), but carry on; use fail to stop.

reportError :: String -> Q () Source

Report an error to the user, but allow the current splice's computation to carry on. To abort the computation, use fail.

reportWarning :: String -> Q () Source

Report a warning to the user, and carry on.

recover Source

Arguments

:: Q a

handler to invoke on failure

-> Q a

computation to run

-> Q a 

Recover from errors raised by reportError or fail.

lookupTypeName :: String -> Q (Maybe Name) Source

Look up the given name in the (type namespace of the) current splice's scope. See Language.Haskell.TH.Syntax for more details.

lookupValueName :: String -> Q (Maybe Name) Source

Look up the given name in the (value namespace of the) current splice's scope. See Language.Haskell.TH.Syntax for more details.

The functions lookupTypeName and lookupValueName provide a way to query the current splice's context for what names are in scope. The function lookupTypeName queries the type namespace, whereas lookupValueName queries the value namespace, but the functions are otherwise identical.

A call lookupValueName s will check if there is a value with name s in scope at the current splice's location. If there is, the Name of this value is returned; if not, then Nothing is returned.

The returned name cannot be "captured". For example:

f = "global"
g = $( do
         Just nm <- lookupValueName "f"
         [| let f = "local" in $( varE nm ) |]

In this case, g = "global"; the call to lookupValueName returned the global f, and this name was not captured by the local definition of f.

The lookup is performed in the context of the top-level splice being run. For example:

f = "global"
g = $( [| let f = "local" in
           $(do
               Just nm <- lookupValueName "f"
               varE nm
            ) |] )

Again in this example, g = "global", because the call to lookupValueName queries the context of the outer-most $(...).

Operators should be queried without any surrounding parentheses, like so:

lookupValueName "+"

Qualified names are also supported, like so:

lookupValueName "Prelude.+"
lookupValueName "Prelude.map"

reify :: Name -> Q Info Source

reify looks up information about the Name.

It is sometimes useful to construct the argument name using lookupTypeName or lookupValueName to ensure that we are reifying from the right namespace. For instance, in this context:

data D = D

which D does reify (mkName "D") return information about? (Answer: D-the-type, but don't rely on it.) To ensure we get information about D-the-value, use lookupValueName:

do
  Just nm <- lookupValueName "D"
  reify nm

and to get information about D-the-type, use lookupTypeName.

reifyFixity :: Name -> Q (Maybe Fixity) Source

reifyFixity nm attempts to find a fixity declaration for nm. For example, if the function foo has the fixity declaration infixr 7 foo, then reifyFixity 'foo would return Just (Fixity 7 InfixR). If the function bar does not have a fixity declaration, then reifyFixity 'bar returns Nothing, so you may assume bar has defaultFixity.

reifyInstances :: Name -> [Type] -> Q [InstanceDec] Source

reifyInstances nm tys returns a list of visible instances of nm tys. That is, if nm is the name of a type class, then all instances of this class at the types tys are returned. Alternatively, if nm is the name of a data family or type family, all instances of this family at the types tys are returned.

reifyRoles :: Name -> Q [Role] Source

reifyRoles nm returns the list of roles associated with the parameters of the tycon nm. Fails if nm cannot be found or is not a tycon. The returned list should never contain InferR.

reifyAnnotations :: Data a => AnnLookup -> Q [a] Source

reifyAnnotations target returns the list of annotations associated with target. Only the annotations that are appropriately typed is returned. So if you have Int and String annotations for the same target, you have to call this function twice.

reifyModule :: Module -> Q ModuleInfo Source

reifyModule mod looks up information about module mod. To look up the current module, call this function with the return value of thisModule.

reifyConStrictness :: Name -> Q [DecidedStrictness] Source

reifyConStrictness nm looks up the strictness information for the fields of the constructor with the name nm. Note that the strictness information that reifyConStrictness returns may not correspond to what is written in the source code. For example, in the following data declaration:

data Pair a = Pair a a

reifyConStrictness would return [DecidedLazy, DecidedLazy] under most circumstances, but it would return [DecidedStrict, DecidedStrict] if the -XStrictData language extension was enabled.

isInstance :: Name -> [Type] -> Q Bool Source

Is the list of instances returned by reifyInstances nonempty?

location :: Q Loc Source

The location at which this computation is spliced.

runIO :: IO a -> Q a Source

The runIO function lets you run an I/O computation in the Q monad. Take care: you are guaranteed the ordering of calls to runIO within a single Q computation, but not about the order in which splices are run.

Note: for various murky reasons, stdout and stderr handles are not necessarily flushed when the compiler finishes running, so you should flush them yourself.

addDependentFile :: FilePath -> Q () Source

Record external files that runIO is using (dependent upon). The compiler can then recognize that it should re-compile the Haskell file when an external file changes.

Expects an absolute file path.

Notes:

  • ghc -M does not know about these dependencies - it does not execute TH.
  • The dependency is based on file content, not a modification time

addTopDecls :: [Dec] -> Q () Source

Add additional top-level declarations. The added declarations will be type checked along with the current declaration group.

addModFinalizer :: Q () -> Q () Source

Add a finalizer that will run in the Q monad after the current module has been type checked. This only makes sense when run within a top-level splice.

getQ :: Typeable a => Q (Maybe a) Source

Get state from the Q monad.

putQ :: Typeable a => a -> Q () Source

Replace the state in the Q monad.

isExtEnabled :: Extension -> Q Bool Source

Determine whether the given language extension is enabled in the Q monad.

extsEnabled :: Q [Extension] Source

List all enabled language extensions.

returnQ :: a -> Q a Source

bindQ :: Q a -> (a -> Q b) -> Q b Source

sequenceQ :: [Q a] -> Q [a] Source

class Lift t where Source

A Lift instance can have any of its values turned into a Template Haskell expression. This is needed when a value used within a Template Haskell quotation is bound outside the Oxford brackets ([| ... |]) but not at the top level. As an example:

add1 :: Int -> Q Exp
add1 x = [| x + 1 |]

Template Haskell has no way of knowing what value x will take on at splice-time, so it requires the type of x to be an instance of Lift.

Lift instances can be derived automatically by use of the -XDeriveLift GHC language extension:

{-# LANGUAGE DeriveLift #-}
module Foo where

import Language.Haskell.TH.Syntax

data Bar a = Bar1 a (Bar a) | Bar2 String
  deriving Lift

Methods

lift :: t -> Q Exp Source

Turn a value into a Template Haskell expression, suitable for use in a splice.

lift :: Data t => t -> Q Exp Source

Turn a value into a Template Haskell expression, suitable for use in a splice.

Instances

Lift Bool 

Methods

lift :: Bool -> Q Exp Source

Lift Char 

Methods

lift :: Char -> Q Exp Source

Lift Double 

Methods

lift :: Double -> Q Exp Source

Lift Float 

Methods

lift :: Float -> Q Exp Source

Lift Int 

Methods

lift :: Int -> Q Exp Source

Lift Int8 

Methods

lift :: Int8 -> Q Exp Source

Lift Int16 

Methods

lift :: Int16 -> Q Exp Source

Lift Int32 

Methods

lift :: Int32 -> Q Exp Source

Lift Int64 

Methods

lift :: Int64 -> Q Exp Source

Lift Integer 

Methods

lift :: Integer -> Q Exp Source

Lift Word 

Methods

lift :: Word -> Q Exp Source

Lift Word8 

Methods

lift :: Word8 -> Q Exp Source

Lift Word16 

Methods

lift :: Word16 -> Q Exp Source

Lift Word32 

Methods

lift :: Word32 -> Q Exp Source

Lift Word64 

Methods

lift :: Word64 -> Q Exp Source

Lift () 

Methods

lift :: () -> Q Exp Source

Lift Natural 

Methods

lift :: Natural -> Q Exp Source

Lift a => Lift [a] 

Methods

lift :: [a] -> Q Exp Source

Lift a => Lift (Maybe a) 

Methods

lift :: Maybe a -> Q Exp Source

Integral a => Lift (Ratio a) 

Methods

lift :: Ratio a -> Q Exp Source

(Lift a, Lift b) => Lift (Either a b) 

Methods

lift :: Either a b -> Q Exp Source

(Lift a, Lift b) => Lift (a, b) 

Methods

lift :: (a, b) -> Q Exp Source

(Lift a, Lift b, Lift c) => Lift (a, b, c) 

Methods

lift :: (a, b, c) -> Q Exp Source

(Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) 

Methods

lift :: (a, b, c, d) -> Q Exp Source

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) 

Methods

lift :: (a, b, c, d, e) -> Q Exp Source

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (a, b, c, d, e, f) 

Methods

lift :: (a, b, c, d, e, f) -> Q Exp Source

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift (a, b, c, d, e, f, g) 

Methods

lift :: (a, b, c, d, e, f, g) -> Q Exp Source

dataToQa :: forall a k q. Data a => (Name -> k) -> (Lit -> Q q) -> (k -> [Q q] -> Q q) -> (forall b. Data b => b -> Maybe (Q q)) -> a -> Q q Source

dataToQa is an internal utility function for constructing generic conversion functions from types with Data instances to various quasi-quoting representations. See the source of dataToExpQ and dataToPatQ for two example usages: mkCon, mkLit and appQ are overloadable to account for different syntax for expressions and patterns; antiQ allows you to override type-specific cases, a common usage is just const Nothing, which results in no overloading.

dataToExpQ :: Data a => (forall b. Data b => b -> Maybe (Q Exp)) -> a -> Q Exp Source

dataToExpQ converts a value to a 'Q Exp' representation of the same value, in the SYB style. It is generalized to take a function override type-specific cases; see liftData for a more commonly used variant.

liftData :: Data a => a -> Q Exp Source

liftData is a variant of lift in the Lift type class which works for any type with a Data instance.

dataToPatQ :: Data a => (forall b. Data b => b -> Maybe (Q Pat)) -> a -> Q Pat Source

dataToPatQ converts a value to a 'Q Pat' representation of the same value, in the SYB style. It takes a function to handle type-specific cases, alternatively, pass const Nothing to get default behavior.

newtype ModName Source

Constructors

ModName String 

Instances

Eq ModName 

Methods

(==) :: ModName -> ModName -> Bool

(/=) :: ModName -> ModName -> Bool

Data ModName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModName -> c ModName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModName Source

toConstr :: ModName -> Constr Source

dataTypeOf :: ModName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c ModName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModName) Source

gmapT :: (forall b. Data b => b -> b) -> ModName -> ModName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ModName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source

Ord ModName 
Show ModName 
Generic ModName 

Associated Types

type Rep ModName :: * -> * Source

type Rep ModName = D1 (MetaData "ModName" "Language.Haskell.TH.Syntax" "template-haskell" True) (C1 (MetaCons "ModName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) 

newtype PkgName Source

Constructors

PkgName String 

Instances

Eq PkgName 

Methods

(==) :: PkgName -> PkgName -> Bool

(/=) :: PkgName -> PkgName -> Bool

Data PkgName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgName -> c PkgName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgName Source

toConstr :: PkgName -> Constr Source

dataTypeOf :: PkgName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c PkgName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgName) Source

gmapT :: (forall b. Data b => b -> b) -> PkgName -> PkgName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> PkgName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source

Ord PkgName 
Show PkgName 
Generic PkgName 

Associated Types

type Rep PkgName :: * -> * Source

type Rep PkgName = D1 (MetaData "PkgName" "Language.Haskell.TH.Syntax" "template-haskell" True) (C1 (MetaCons "PkgName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) 

data Module Source

Obtained from reifyModule and thisModule.

Constructors

Module PkgName ModName 

Instances

Eq Module 

Methods

(==) :: Module -> Module -> Bool

(/=) :: Module -> Module -> Bool

Data Module 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module Source

toConstr :: Module -> Constr Source

dataTypeOf :: Module -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Module) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) Source

gmapT :: (forall b. Data b => b -> b) -> Module -> Module Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source

Ord Module 
Show Module 
Generic Module 

Associated Types

type Rep Module :: * -> * Source

Ppr Module 
type Rep Module = D1 (MetaData "Module" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Module" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModName)))) 

newtype OccName Source

Constructors

OccName String 

Instances

Eq OccName 

Methods

(==) :: OccName -> OccName -> Bool

(/=) :: OccName -> OccName -> Bool

Data OccName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName Source

toConstr :: OccName -> Constr Source

dataTypeOf :: OccName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c OccName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) Source

gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source

Ord OccName 
Show OccName 
Generic OccName 

Associated Types

type Rep OccName :: * -> * Source

type Rep OccName = D1 (MetaData "OccName" "Language.Haskell.TH.Syntax" "template-haskell" True) (C1 (MetaCons "OccName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) 

Much of Name API is concerned with the problem of name capture, which can be seen in the following example.

f expr = [| let x = 0 in $expr |]
...
g x = $( f [| x |] )
h y = $( f [| y |] )

A naive desugaring of this would yield:

g x = let x = 0 in x
h y = let x = 0 in y

All of a sudden, g and h have different meanings! In this case, we say that the x in the RHS of g has been captured by the binding of x in f.

What we actually want is for the x in f to be distinct from the x in g, so we get the following desugaring:

g x = let x' = 0 in x
h y = let x' = 0 in y

which avoids name capture as desired.

In the general case, we say that a Name can be captured if the thing it refers to can be changed by adding new declarations.

data Name Source

An abstract type representing names in the syntax tree.

Names can be constructed in several ways, which come with different name-capture guarantees (see Language.Haskell.TH.Syntax for an explanation of name capture):

  • the built-in syntax 'f and ''T can be used to construct names, The expression 'f gives a Name which refers to the value f currently in scope, and ''T gives a Name which refers to the type T currently in scope. These names can never be captured.
  • lookupValueName and lookupTypeName are similar to 'f and ''T respectively, but the Names are looked up at the point where the current splice is being run. These names can never be captured.
  • newName monadically generates a new name, which can never be captured.
  • mkName generates a capturable name.

Names constructed using newName and mkName may be used in bindings (such as let x = ... or x -> ...), but names constructed using lookupValueName, lookupTypeName, 'f, ''T may not.

Constructors

Name OccName NameFlavour 

Instances

Eq Name 

Methods

(==) :: Name -> Name -> Bool

(/=) :: Name -> Name -> Bool

Data Name 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name Source

toConstr :: Name -> Constr Source

dataTypeOf :: Name -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Name) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) Source

gmapT :: (forall b. Data b => b -> b) -> Name -> Name Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source

Ord Name 

Methods

compare :: Name -> Name -> Ordering

(<) :: Name -> Name -> Bool

(<=) :: Name -> Name -> Bool

(>) :: Name -> Name -> Bool

(>=) :: Name -> Name -> Bool

max :: Name -> Name -> Name

min :: Name -> Name -> Name

Show Name 
Generic Name 

Associated Types

type Rep Name :: * -> * Source

Methods

from :: Name -> Rep Name x Source

to :: Rep Name x -> Name Source

Ppr Name 

Methods

ppr :: Name -> Doc Source

ppr_list :: [Name] -> Doc Source

type Rep Name = D1 (MetaData "Name" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Name" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OccName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameFlavour)))) 

data NameFlavour Source

Constructors

NameS

An unqualified name; dynamically bound

NameQ ModName

A qualified name; dynamically bound

NameU !Int

A unique local name

NameL !Int

Local name bound outside of the TH AST

NameG NameSpace PkgName ModName

Global name bound outside of the TH AST: An original name (occurrences only, not binders) Need the namespace too to be sure which thing we are naming

Instances

Eq NameFlavour 
Data NameFlavour 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameFlavour -> c NameFlavour Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameFlavour Source

toConstr :: NameFlavour -> Constr Source

dataTypeOf :: NameFlavour -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c NameFlavour) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameFlavour) Source

gmapT :: (forall b. Data b => b -> b) -> NameFlavour -> NameFlavour Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameFlavour -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameFlavour -> r Source

gmapQ :: (forall d. Data d => d -> u) -> NameFlavour -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameFlavour -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour Source

Ord NameFlavour 
Show NameFlavour 
Generic NameFlavour 

Associated Types

type Rep NameFlavour :: * -> * Source

type Rep NameFlavour = D1 (MetaData "NameFlavour" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "NameS" PrefixI False) U1) (C1 (MetaCons "NameQ" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModName)))) ((:+:) (C1 (MetaCons "NameU" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))) ((:+:) (C1 (MetaCons "NameL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))) (C1 (MetaCons "NameG" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameSpace)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModName)))))))) 

data NameSpace Source

Constructors

VarName

Variables

DataName

Data constructors

TcClsName

Type constructors and classes; Haskell has them in the same name space for now.

Instances

Eq NameSpace 
Data NameSpace 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameSpace -> c NameSpace Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameSpace Source

toConstr :: NameSpace -> Constr Source

dataTypeOf :: NameSpace -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c NameSpace) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameSpace) Source

gmapT :: (forall b. Data b => b -> b) -> NameSpace -> NameSpace Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r Source

gmapQ :: (forall d. Data d => d -> u) -> NameSpace -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameSpace -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source

Ord NameSpace 
Show NameSpace 
Generic NameSpace 

Associated Types

type Rep NameSpace :: * -> * Source

type Rep NameSpace = D1 (MetaData "NameSpace" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "VarName" PrefixI False) U1) ((:+:) (C1 (MetaCons "DataName" PrefixI False) U1) (C1 (MetaCons "TcClsName" PrefixI False) U1))) 

type Uniq = Int Source

nameBase :: Name -> String Source

The name without its module prefix.

Examples

>>> nameBase ''Data.Either.Either
"Either"
>>> nameBase (mkName "foo")
"foo"
>>> nameBase (mkName "Module.foo")
"foo"

nameModule :: Name -> Maybe String Source

Module prefix of a name, if it exists.

Examples

>>> nameModule ''Data.Either.Either
Just "Data.Either"
>>> nameModule (mkName "foo")
Nothing
>>> nameModule (mkName "Module.foo")
Just "Module"

namePackage :: Name -> Maybe String Source

A name's package, if it exists.

Examples

>>> namePackage ''Data.Either.Either
Just "base"
>>> namePackage (mkName "foo")
Nothing
>>> namePackage (mkName "Module.foo")
Nothing

nameSpace :: Name -> Maybe NameSpace Source

Returns whether a name represents an occurrence of a top-level variable (VarName), data constructor (DataName), type constructor, or type class (TcClsName). If we can't be sure, it returns Nothing.

Examples

>>> nameSpace 'Prelude.id
Just VarName
>>> nameSpace (mkName "id")
Nothing -- only works for top-level variable names
>>> nameSpace 'Data.Maybe.Just
Just DataName
>>> nameSpace ''Data.Maybe.Maybe
Just TcClsName
>>> nameSpace ''Data.Ord.Ord
Just TcClsName

mkName :: String -> Name Source

Generate a capturable name. Occurrences of such names will be resolved according to the Haskell scoping rules at the occurrence site.

For example:

f = [| pi + $(varE (mkName "pi")) |]
...
g = let pi = 3 in $f

In this case, g is desugared to

g = Prelude.pi + 3

Note that mkName may be used with qualified names:

mkName "Prelude.pi"

See also dyn for a useful combinator. The above example could be rewritten using dyn as

f = [| pi + $(dyn "pi") |]

mkNameU :: String -> Uniq -> Name Source

Only used internally

mkNameL :: String -> Uniq -> Name Source

Only used internally

mkNameG :: NameSpace -> String -> String -> String -> Name Source

Used for 'x etc, but not available to the programmer

data NameIs Source

Constructors

Alone 
Applied 
Infix 

tupleDataName :: Int -> Name Source

Tuple data constructor

tupleTypeName :: Int -> Name Source

Tuple type constructor

unboxedTupleDataName :: Int -> Name Source

Unboxed tuple data constructor

unboxedTupleTypeName :: Int -> Name Source

Unboxed tuple type constructor

data Loc Source

Instances

Eq Loc 

Methods

(==) :: Loc -> Loc -> Bool

(/=) :: Loc -> Loc -> Bool

Data Loc 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc Source

toConstr :: Loc -> Constr Source

dataTypeOf :: Loc -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Loc) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) Source

gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source

Ord Loc 

Methods

compare :: Loc -> Loc -> Ordering

(<) :: Loc -> Loc -> Bool

(<=) :: Loc -> Loc -> Bool

(>) :: Loc -> Loc -> Bool

(>=) :: Loc -> Loc -> Bool

max :: Loc -> Loc -> Loc

min :: Loc -> Loc -> Loc

Show Loc 
Generic Loc 

Associated Types

type Rep Loc :: * -> * Source

Methods

from :: Loc -> Rep Loc x Source

to :: Rep Loc x -> Loc Source

Ppr Loc 

Methods

ppr :: Loc -> Doc Source

ppr_list :: [Loc] -> Doc Source

type Rep Loc = D1 (MetaData "Loc" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Loc" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "loc_filename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "loc_package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "loc_module") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "loc_start") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CharPos)) (S1 (MetaSel (Just Symbol "loc_end") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CharPos)))))) 

type CharPos Source

Arguments

 = (Int, Int)

Line and character position

data Info Source

Obtained from reify in the Q Monad.

Constructors

ClassI Dec [InstanceDec]

A class, with a list of its visible instances

ClassOpI Name Type ParentName

A class method

TyConI Dec

A "plain" type constructor. "Fancier" type constructors are returned using PrimTyConI or FamilyI as appropriate

FamilyI Dec [InstanceDec]

A type or data family, with a list of its visible instances. A closed type family is returned with 0 instances.

PrimTyConI Name Arity Unlifted

A "primitive" type constructor, which can't be expressed with a Dec. Examples: (->), Int#.

DataConI Name Type ParentName

A data constructor

VarI Name Type (Maybe Dec)

A "value" variable (as opposed to a type variable, see TyVarI).

The Maybe Dec field contains Just the declaration which defined the variable -- including the RHS of the declaration -- or else Nothing, in the case where the RHS is unavailable to the compiler. At present, this value is _always_ Nothing: returning the RHS has not yet been implemented because of lack of interest.

TyVarI Name Type

A type variable.

The Type field contains the type which underlies the variable. At present, this is always VarT theName, but future changes may permit refinement of this.

Instances

Eq Info 

Methods

(==) :: Info -> Info -> Bool

(/=) :: Info -> Info -> Bool

Data Info 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Info -> c Info Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Info Source

toConstr :: Info -> Constr Source

dataTypeOf :: Info -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Info) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info) Source

gmapT :: (forall b. Data b => b -> b) -> Info -> Info Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Info -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Info -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Info -> m Info Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info Source

Ord Info 

Methods

compare :: Info -> Info -> Ordering

(<) :: Info -> Info -> Bool

(<=) :: Info -> Info -> Bool

(>) :: Info -> Info -> Bool

(>=) :: Info -> Info -> Bool

max :: Info -> Info -> Info

min :: Info -> Info -> Info

Show Info 
Generic Info 

Associated Types

type Rep Info :: * -> * Source

Methods

from :: Info -> Rep Info x Source

to :: Rep Info x -> Info Source

Ppr Info 

Methods

ppr :: Info -> Doc Source

ppr_list :: [Info] -> Doc Source

type Rep Info = D1 (MetaData "Info" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ClassI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Dec)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [InstanceDec])))) (C1 (MetaCons "ClassOpI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParentName)))))) ((:+:) (C1 (MetaCons "TyConI" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Dec))) (C1 (MetaCons "FamilyI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Dec)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [InstanceDec])))))) ((:+:) ((:+:) (C1 (MetaCons "PrimTyConI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Arity)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Unlifted))))) (C1 (MetaCons "DataConI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParentName)))))) ((:+:) (C1 (MetaCons "VarI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Dec)))))) (C1 (MetaCons "TyVarI" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))))) 

data ModuleInfo Source

Obtained from reifyModule in the Q Monad.

Constructors

ModuleInfo [Module]

Contains the import list of the module.

Instances

Eq ModuleInfo 
Data ModuleInfo 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleInfo -> c ModuleInfo Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleInfo Source

toConstr :: ModuleInfo -> Constr Source

dataTypeOf :: ModuleInfo -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleInfo) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleInfo) Source

gmapT :: (forall b. Data b => b -> b) -> ModuleInfo -> ModuleInfo Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ModuleInfo -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleInfo -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo Source

Ord ModuleInfo 
Show ModuleInfo 
Generic ModuleInfo 

Associated Types

type Rep ModuleInfo :: * -> * Source

Ppr ModuleInfo 
type Rep ModuleInfo = D1 (MetaData "ModuleInfo" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "ModuleInfo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Module]))) 

type ParentName = Name Source

In ClassOpI and DataConI, name of the parent class or type

type Arity = Int Source

In PrimTyConI, arity of the type constructor

type Unlifted = Bool Source

In PrimTyConI, is the type constructor unlifted?

type InstanceDec = Dec Source

InstanceDec desribes a single instance of a class or type function. It is just a Dec, but guaranteed to be one of the following:

data Fixity Source

Constructors

Fixity Int FixityDirection 

Instances

Eq Fixity 

Methods

(==) :: Fixity -> Fixity -> Bool

(/=) :: Fixity -> Fixity -> Bool

Data Fixity 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity Source

toConstr :: Fixity -> Constr Source

dataTypeOf :: Fixity -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) Source

gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source

Ord Fixity 
Show Fixity 
Generic Fixity 

Associated Types

type Rep Fixity :: * -> * Source

type Rep Fixity = D1 (MetaData "Fixity" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Fixity" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FixityDirection)))) 

data FixityDirection Source

Constructors

InfixL 
InfixR 
InfixN 

Instances

Eq FixityDirection 
Data FixityDirection 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection Source

toConstr :: FixityDirection -> Constr Source

dataTypeOf :: FixityDirection -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) Source

gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection Source

Ord FixityDirection 
Show FixityDirection 
Generic FixityDirection 
type Rep FixityDirection = D1 (MetaData "FixityDirection" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "InfixL" PrefixI False) U1) ((:+:) (C1 (MetaCons "InfixR" PrefixI False) U1) (C1 (MetaCons "InfixN" PrefixI False) U1))) 

maxPrecedence :: Int Source

Highest allowed operator precedence for Fixity constructor (answer: 9)

defaultFixity :: Fixity Source

Default fixity: infixl 9

When implementing antiquotation for quasiquoters, one often wants to parse strings into expressions:

parse :: String -> Maybe Exp

But how should we parse a + b * c? If we don't know the fixities of + and *, we don't know whether to parse it as a + (b * c) or (a + b) * c.

In cases like this, use UInfixE, UInfixP, or UInfixT, which stand for "unresolved infix expressionpatterntype", respectively. When the compiler is given a splice containing a tree of UInfixE applications such as

UInfixE
  (UInfixE e1 op1 e2)
  op2
  (UInfixE e3 op3 e4)

it will look up and the fixities of the relevant operators and reassociate the tree as necessary.

  • trees will not be reassociated across ParensE, ParensP, or ParensT, which are of use for parsing expressions like
(a + b * c) + d * e
  • InfixE, InfixP, and InfixT expressions are never reassociated.
  • The UInfixE constructor doesn't support sections. Sections such as (a *) have no ambiguity, so InfixE suffices. For longer sections such as (a + b * c -), use an InfixE constructor for the outer-most section, and use UInfixE constructors for all other operators:
InfixE
  Just (UInfixE ...a + b * c...)
  op
  Nothing

Sections such as (a + b +) and ((a + b) +) should be rendered into Exps differently:

(+ a + b)   ---> InfixE Nothing + (Just $ UInfixE a + b)
                   -- will result in a fixity error if (+) is left-infix
(+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
                   -- no fixity errors
  • Quoted expressions such as
[| a * b + c |] :: Q Exp
[p| a : b : c |] :: Q Pat
[t| T + T |] :: Q Type

will never contain UInfixE, UInfixP, UInfixT, InfixT, ParensE, ParensP, or ParensT constructors.

data Lit Source

Constructors

CharL Char 
StringL String 
IntegerL Integer

Used for overloaded and non-overloaded literals. We don't have a good way to represent non-overloaded literals at the moment. Maybe that doesn't matter?

RationalL Rational 
IntPrimL Integer 
WordPrimL Integer 
FloatPrimL Rational 
DoublePrimL Rational 
StringPrimL [Word8]

A primitive C-style string, type Addr#

CharPrimL Char 

Instances

Eq Lit 

Methods

(==) :: Lit -> Lit -> Bool

(/=) :: Lit -> Lit -> Bool

Data Lit 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lit -> c Lit Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lit Source

toConstr :: Lit -> Constr Source

dataTypeOf :: Lit -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Lit) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lit) Source

gmapT :: (forall b. Data b => b -> b) -> Lit -> Lit Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lit -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lit -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Lit -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lit -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lit -> m Lit Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lit -> m Lit Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lit -> m Lit Source

Ord Lit 

Methods

compare :: Lit -> Lit -> Ordering

(<) :: Lit -> Lit -> Bool

(<=) :: Lit -> Lit -> Bool

(>) :: Lit -> Lit -> Bool

(>=) :: Lit -> Lit -> Bool

max :: Lit -> Lit -> Lit

min :: Lit -> Lit -> Lit

Show Lit 
Generic Lit 

Associated Types

type Rep Lit :: * -> * Source

Methods

from :: Lit -> Rep Lit x Source

to :: Rep Lit x -> Lit Source

Ppr Lit 

Methods

ppr :: Lit -> Doc Source

ppr_list :: [Lit] -> Doc Source

type Rep Lit = D1 (MetaData "Lit" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CharL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))) (C1 (MetaCons "StringL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (C1 (MetaCons "IntegerL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) ((:+:) (C1 (MetaCons "RationalL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational))) (C1 (MetaCons "IntPrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))))) ((:+:) ((:+:) (C1 (MetaCons "WordPrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "FloatPrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational)))) ((:+:) (C1 (MetaCons "DoublePrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational))) ((:+:) (C1 (MetaCons "StringPrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Word8]))) (C1 (MetaCons "CharPrimL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))))))) 

data Pat Source

Pattern in Haskell given in {}

Constructors

LitP Lit
{ 5 or 'c' }
VarP Name
{ x }
TupP [Pat]
{ (p1,p2) }
UnboxedTupP [Pat]
{ (# p1,p2 #) }
ConP Name [Pat]
data T1 = C1 t1 t2; {C1 p1 p1} = e
InfixP Pat Name Pat
foo ({x :+ y}) = e
UInfixP Pat Name Pat
foo ({x :+ y}) = e

See Language.Haskell.TH.Syntax

ParensP Pat
{(p)}

See Language.Haskell.TH.Syntax

TildeP Pat
{ ~p }
BangP Pat
{ !p }
AsP Name Pat
{ x @ p }
WildP
{ _ }
RecP Name [FieldPat]
f (Pt { pointx = x }) = g x
ListP [Pat]
{ [1,2,3] }
SigP Pat Type
{ p :: t }
ViewP Exp Pat
{ e -> p }

Instances

Eq Pat 

Methods

(==) :: Pat -> Pat -> Bool

(/=) :: Pat -> Pat -> Bool

Data Pat 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat -> c Pat Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pat Source

toConstr :: Pat -> Constr Source

dataTypeOf :: Pat -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Pat) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pat) Source

gmapT :: (forall b. Data b => b -> b) -> Pat -> Pat Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Pat -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat -> m Pat Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat Source

Ord Pat 

Methods

compare :: Pat -> Pat -> Ordering

(<) :: Pat -> Pat -> Bool

(<=) :: Pat -> Pat -> Bool

(>) :: Pat -> Pat -> Bool

(>=) :: Pat -> Pat -> Bool

max :: Pat -> Pat -> Pat

min :: Pat -> Pat -> Pat

Show Pat 
Generic Pat 

Associated Types

type Rep Pat :: * -> * Source

Methods

from :: Pat -> Rep Pat x Source

to :: Rep Pat x -> Pat Source

Ppr Pat 

Methods

ppr :: Pat -> Doc Source

ppr_list :: [Pat] -> Doc Source

type Rep Pat = D1 (MetaData "Pat" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LitP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Lit))) (C1 (MetaCons "VarP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))) ((:+:) (C1 (MetaCons "TupP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat]))) (C1 (MetaCons "UnboxedTupP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat]))))) ((:+:) ((:+:) (C1 (MetaCons "ConP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat])))) (C1 (MetaCons "InfixP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)))))) ((:+:) (C1 (MetaCons "UInfixP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat))))) (C1 (MetaCons "ParensP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TildeP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat))) (C1 (MetaCons "BangP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)))) ((:+:) (C1 (MetaCons "AsP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)))) (C1 (MetaCons "WildP" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RecP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FieldPat])))) (C1 (MetaCons "ListP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat])))) ((:+:) (C1 (MetaCons "SigP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) (C1 (MetaCons "ViewP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)))))))) 

data Match Source

Constructors

Match Pat Body [Dec]
case e of { pat -> body where decs }

Instances

Eq Match 

Methods

(==) :: Match -> Match -> Bool

(/=) :: Match -> Match -> Bool

Data Match 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match -> c Match Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Match Source

toConstr :: Match -> Constr Source

dataTypeOf :: Match -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Match) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Match) Source

gmapT :: (forall b. Data b => b -> b) -> Match -> Match Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Match -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match -> m Match Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match Source

Ord Match 

Methods

compare :: Match -> Match -> Ordering

(<) :: Match -> Match -> Bool

(<=) :: Match -> Match -> Bool

(>) :: Match -> Match -> Bool

(>=) :: Match -> Match -> Bool

max :: Match -> Match -> Match

min :: Match -> Match -> Match

Show Match 
Generic Match 

Associated Types

type Rep Match :: * -> * Source

Methods

from :: Match -> Rep Match x Source

to :: Rep Match x -> Match Source

Ppr Match 

Methods

ppr :: Match -> Doc Source

ppr_list :: [Match] -> Doc Source

type Rep Match = D1 (MetaData "Match" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Match" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Body)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec]))))) 

data Clause Source

Constructors

Clause [Pat] Body [Dec]
f { p1 p2 = body where decs }

Instances

Eq Clause 

Methods

(==) :: Clause -> Clause -> Bool

(/=) :: Clause -> Clause -> Bool

Data Clause 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Clause -> c Clause Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Clause Source

toConstr :: Clause -> Constr Source

dataTypeOf :: Clause -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Clause) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Clause) Source

gmapT :: (forall b. Data b => b -> b) -> Clause -> Clause Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Clause -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Clause -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source

Ord Clause 
Show Clause 
Generic Clause 

Associated Types

type Rep Clause :: * -> * Source

Ppr Clause 
type Rep Clause = D1 (MetaData "Clause" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Clause" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Body)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec]))))) 

data Exp Source

Constructors

VarE Name
{ x }
ConE Name
data T1 = C1 t1 t2; p = {C1} e1 e2
LitE Lit
{ 5 or 'c'}
AppE Exp Exp
{ f x }
InfixE (Maybe Exp) Exp (Maybe Exp)
{x + y} or {(x+)} or {(+ x)} or {(+)}
UInfixE Exp Exp Exp
{x + y}

See Language.Haskell.TH.Syntax

ParensE Exp
{ (e) }

See Language.Haskell.TH.Syntax

LamE [Pat] Exp
{ \ p1 p2 -> e }
LamCaseE [Match]
{ \case m1; m2 }
TupE [Exp]
{ (e1,e2) }
UnboxedTupE [Exp]
{ (# e1,e2 #) }
CondE Exp Exp Exp
{ if e1 then e2 else e3 }
MultiIfE [(Guard, Exp)]
{ if | g1 -> e1 | g2 -> e2 }
LetE [Dec] Exp
{ let x=e1;   y=e2 in e3 }
CaseE Exp [Match]
{ case e of m1; m2 }
DoE [Stmt]
{ do { p <- e1; e2 }  }
CompE [Stmt]
{ [ (x,y) | x <- xs, y <- ys ] }

The result expression of the comprehension is the last of the Stmts, and should be a NoBindS.

E.g. translation:

[ f x | x <- xs ]
CompE [BindS (VarP x) (VarE xs), NoBindS (AppE (VarE f) (VarE x))]
ArithSeqE Range
{ [ 1 ,2 .. 10 ] }
ListE [Exp]
{ [1,2,3] }
SigE Exp Type
{ e :: t }
RecConE Name [FieldExp]
{ T { x = y, z = w } }
RecUpdE Exp [FieldExp]
{ (f x) { z = w } }
StaticE Exp
{ static e }
UnboundVarE Name

{ _x } (hole)

Instances

Eq Exp 

Methods

(==) :: Exp -> Exp -> Bool

(/=) :: Exp -> Exp -> Bool

Data Exp 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp Source

toConstr :: Exp -> Constr Source

dataTypeOf :: Exp -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Exp) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) Source

gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source

Ord Exp 

Methods

compare :: Exp -> Exp -> Ordering

(<) :: Exp -> Exp -> Bool

(<=) :: Exp -> Exp -> Bool

(>) :: Exp -> Exp -> Bool

(>=) :: Exp -> Exp -> Bool

max :: Exp -> Exp -> Exp

min :: Exp -> Exp -> Exp

Show Exp 
Generic Exp 

Associated Types

type Rep Exp :: * -> * Source

Methods

from :: Exp -> Rep Exp x Source

to :: Rep Exp x -> Exp Source

Ppr Exp 

Methods

ppr :: Exp -> Doc Source

ppr_list :: [Exp] -> Doc Source

type Rep Exp = D1 (MetaData "Exp" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "VarE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) ((:+:) (C1 (MetaCons "ConE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "LitE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Lit))))) ((:+:) (C1 (MetaCons "AppE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) ((:+:) (C1 (MetaCons "InfixE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp)))))) (C1 (MetaCons "UInfixE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))) ((:+:) ((:+:) (C1 (MetaCons "ParensE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) ((:+:) (C1 (MetaCons "LamE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pat])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "LamCaseE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Match]))))) ((:+:) (C1 (MetaCons "TupE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exp]))) ((:+:) (C1 (MetaCons "UnboxedTupE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exp]))) (C1 (MetaCons "CondE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MultiIfE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Guard, Exp)]))) ((:+:) (C1 (MetaCons "LetE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "CaseE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Match])))))) ((:+:) (C1 (MetaCons "DoE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Stmt]))) ((:+:) (C1 (MetaCons "CompE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Stmt]))) (C1 (MetaCons "ArithSeqE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Range)))))) ((:+:) ((:+:) (C1 (MetaCons "ListE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exp]))) ((:+:) (C1 (MetaCons "SigE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) (C1 (MetaCons "RecConE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FieldExp])))))) ((:+:) (C1 (MetaCons "RecUpdE" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FieldExp])))) ((:+:) (C1 (MetaCons "StaticE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) (C1 (MetaCons "UnboundVarE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))))))) 

data Body Source

Constructors

GuardedB [(Guard, Exp)]
f p { | e1 = e2
      | e3 = e4 }
 where ds
NormalB Exp
f p { = e } where ds

Instances

Eq Body 

Methods

(==) :: Body -> Body -> Bool

(/=) :: Body -> Body -> Bool

Data Body 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Body -> c Body Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Body Source

toConstr :: Body -> Constr Source

dataTypeOf :: Body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Body) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Body) Source

gmapT :: (forall b. Data b => b -> b) -> Body -> Body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Body -> m Body Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body Source

Ord Body 

Methods

compare :: Body -> Body -> Ordering

(<) :: Body -> Body -> Bool

(<=) :: Body -> Body -> Bool

(>) :: Body -> Body -> Bool

(>=) :: Body -> Body -> Bool

max :: Body -> Body -> Body

min :: Body -> Body -> Body

Show Body 
Generic Body 

Associated Types

type Rep Body :: * -> * Source

Methods

from :: Body -> Rep Body x Source

to :: Rep Body x -> Body Source

type Rep Body = D1 (MetaData "Body" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "GuardedB" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Guard, Exp)]))) (C1 (MetaCons "NormalB" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) 

data Guard Source

Constructors

NormalG Exp
f x { | odd x } = x
PatG [Stmt]
f x { | Just y <- x, Just z <- y } = z

Instances

Eq Guard 

Methods

(==) :: Guard -> Guard -> Bool

(/=) :: Guard -> Guard -> Bool

Data Guard 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Guard -> c Guard Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Guard Source

toConstr :: Guard -> Constr Source

dataTypeOf :: Guard -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Guard) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Guard) Source

gmapT :: (forall b. Data b => b -> b) -> Guard -> Guard Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Guard -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Guard -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source

Ord Guard 

Methods

compare :: Guard -> Guard -> Ordering

(<) :: Guard -> Guard -> Bool

(<=) :: Guard -> Guard -> Bool

(>) :: Guard -> Guard -> Bool

(>=) :: Guard -> Guard -> Bool

max :: Guard -> Guard -> Guard

min :: Guard -> Guard -> Guard

Show Guard 
Generic Guard 

Associated Types

type Rep Guard :: * -> * Source

Methods

from :: Guard -> Rep Guard x Source

to :: Rep Guard x -> Guard Source

type Rep Guard = D1 (MetaData "Guard" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NormalG" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) (C1 (MetaCons "PatG" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Stmt])))) 

data Stmt Source

Constructors

BindS Pat Exp 
LetS [Dec] 
NoBindS Exp 
ParS [[Stmt]] 

Instances

Eq Stmt 

Methods

(==) :: Stmt -> Stmt -> Bool

(/=) :: Stmt -> Stmt -> Bool

Data Stmt 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt -> c Stmt Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stmt Source

toConstr :: Stmt -> Constr Source

dataTypeOf :: Stmt -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Stmt) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stmt) Source

gmapT :: (forall b. Data b => b -> b) -> Stmt -> Stmt Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Stmt -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt Source

Ord Stmt 

Methods

compare :: Stmt -> Stmt -> Ordering

(<) :: Stmt -> Stmt -> Bool

(<=) :: Stmt -> Stmt -> Bool

(>) :: Stmt -> Stmt -> Bool

(>=) :: Stmt -> Stmt -> Bool

max :: Stmt -> Stmt -> Stmt

min :: Stmt -> Stmt -> Stmt

Show Stmt 
Generic Stmt 

Associated Types

type Rep Stmt :: * -> * Source

Methods

from :: Stmt -> Rep Stmt x Source

to :: Rep Stmt x -> Stmt Source

Ppr Stmt 

Methods

ppr :: Stmt -> Doc Source

ppr_list :: [Stmt] -> Doc Source

type Rep Stmt = D1 (MetaData "Stmt" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "BindS" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "LetS" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec])))) ((:+:) (C1 (MetaCons "NoBindS" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) (C1 (MetaCons "ParS" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Stmt]]))))) 

data Range Source

Instances

Eq Range 

Methods

(==) :: Range -> Range -> Bool

(/=) :: Range -> Range -> Bool

Data Range 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Range -> c Range Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Range Source

toConstr :: Range -> Constr Source

dataTypeOf :: Range -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Range) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Range) Source

gmapT :: (forall b. Data b => b -> b) -> Range -> Range Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Range -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Range -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Range -> m Range Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range Source

Ord Range 

Methods

compare :: Range -> Range -> Ordering

(<) :: Range -> Range -> Bool

(<=) :: Range -> Range -> Bool

(>) :: Range -> Range -> Bool

(>=) :: Range -> Range -> Bool

max :: Range -> Range -> Range

min :: Range -> Range -> Range

Show Range 
Generic Range 

Associated Types

type Rep Range :: * -> * Source

Methods

from :: Range -> Rep Range x Source

to :: Rep Range x -> Range Source

Ppr Range 

Methods

ppr :: Range -> Doc Source

ppr_list :: [Range] -> Doc Source

type Rep Range = D1 (MetaData "Range" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "FromR" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) (C1 (MetaCons "FromThenR" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "FromToR" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "FromThenToR" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))) 

data Dec Source

Constructors

FunD Name [Clause]
{ f p1 p2 = b where decs }
ValD Pat Body [Dec]
{ p = b where decs }
DataD Cxt Name [TyVarBndr] (Maybe Kind) [Con] Cxt
{ data Cxt x => T x = A x | B (T x)
       deriving (Z,W)}
NewtypeD Cxt Name [TyVarBndr] (Maybe Kind) Con Cxt
{ newtype Cxt x => T x = A (B x)
       deriving (Z,W Q)}
TySynD Name [TyVarBndr] Type
{ type T x = (x,x) }
ClassD Cxt Name [TyVarBndr] [FunDep] [Dec]
{ class Eq a => Ord a where ds }
InstanceD Cxt Type [Dec]
{ instance Show w => Show [w]
       where ds }
SigD Name Type
{ length :: [a] -> Int }
ForeignD Foreign
{ foreign import ... }
{ foreign export ... }
InfixD Fixity Name
{ infix 3 foo }
PragmaD Pragma
{ {-# INLINE [1] foo #-} }
DataFamilyD Name [TyVarBndr] (Maybe Kind)
{ data family T a b c :: * }
DataInstD Cxt Name [Type] (Maybe Kind) [Con] Cxt
{ data instance Cxt x => T [x]
       = A x | B (T x) deriving (Z,W)}
NewtypeInstD Cxt Name [Type] (Maybe Kind) Con Cxt
{ newtype instance Cxt x => T [x]
        = A (B x) deriving (Z,W)}
TySynInstD Name TySynEqn
{ type instance ... }
OpenTypeFamilyD TypeFamilyHead
{ type family T a b c = (r :: *) | r -> a b }
ClosedTypeFamilyD TypeFamilyHead [TySynEqn]
{ type family F a b = (r :: *) | r -> a where ... }
RoleAnnotD Name [Role]
{ type role T nominal representational }
StandaloneDerivD Cxt Type
{ deriving instance Ord a => Ord (Foo a) }
DefaultSigD Name Type
{ default size :: Data a => a -> Int }

Instances

Eq Dec 

Methods

(==) :: Dec -> Dec -> Bool

(/=) :: Dec -> Dec -> Bool

Data Dec 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dec -> c Dec Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dec Source

toConstr :: Dec -> Constr Source

dataTypeOf :: Dec -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Dec) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dec) Source

gmapT :: (forall b. Data b => b -> b) -> Dec -> Dec Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dec -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dec -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Dec -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dec -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dec -> m Dec Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dec -> m Dec Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dec -> m Dec Source

Ord Dec 

Methods

compare :: Dec -> Dec -> Ordering

(<) :: Dec -> Dec -> Bool

(<=) :: Dec -> Dec -> Bool

(>) :: Dec -> Dec -> Bool

(>=) :: Dec -> Dec -> Bool

max :: Dec -> Dec -> Dec

min :: Dec -> Dec -> Dec

Show Dec 
Generic Dec 

Associated Types

type Rep Dec :: * -> * Source

Methods

from :: Dec -> Rep Dec x Source

to :: Rep Dec x -> Dec Source

Ppr Dec 

Methods

ppr :: Dec -> Doc Source

ppr_list :: [Dec] -> Doc Source

type Rep Dec = D1 (MetaData "Dec" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FunD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Clause])))) (C1 (MetaCons "ValD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pat)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Body)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec])))))) ((:+:) (C1 (MetaCons "DataD" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Con])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)))))) ((:+:) (C1 (MetaCons "NewtypeD" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Con)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)))))) (C1 (MetaCons "TySynD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))))) ((:+:) ((:+:) (C1 (MetaCons "ClassD" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FunDep])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec])))))) (C1 (MetaCons "InstanceD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dec])))))) ((:+:) (C1 (MetaCons "SigD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) ((:+:) (C1 (MetaCons "ForeignD" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Foreign))) (C1 (MetaCons "InfixD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fixity)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PragmaD" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pragma))) (C1 (MetaCons "DataFamilyD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind))))))) ((:+:) (C1 (MetaCons "DataInstD" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type])))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Con])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)))))) ((:+:) (C1 (MetaCons "NewtypeInstD" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type])))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Con)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)))))) (C1 (MetaCons "TySynInstD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TySynEqn))))))) ((:+:) ((:+:) (C1 (MetaCons "OpenTypeFamilyD" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeFamilyHead))) (C1 (MetaCons "ClosedTypeFamilyD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeFamilyHead)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TySynEqn]))))) ((:+:) (C1 (MetaCons "RoleAnnotD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Role])))) ((:+:) (C1 (MetaCons "StandaloneDerivD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) (C1 (MetaCons "DefaultSigD" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))))))) 

data TypeFamilyHead Source

Common elements of OpenTypeFamilyD and ClosedTypeFamilyD. By analogy with with "head" for type classes and type class instances as defined in Type classes: an exploration of the design space, the TypeFamilyHead is defined to be the elements of the declaration between type family and where.

Instances

Eq TypeFamilyHead 
Data TypeFamilyHead 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeFamilyHead -> c TypeFamilyHead Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeFamilyHead Source

toConstr :: TypeFamilyHead -> Constr Source

dataTypeOf :: TypeFamilyHead -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TypeFamilyHead) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeFamilyHead) Source

gmapT :: (forall b. Data b => b -> b) -> TypeFamilyHead -> TypeFamilyHead Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamilyHead -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamilyHead -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TypeFamilyHead -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeFamilyHead -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead Source

Ord TypeFamilyHead 
Show TypeFamilyHead 
Generic TypeFamilyHead 
type Rep TypeFamilyHead = D1 (MetaData "TypeFamilyHead" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "TypeFamilyHead" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr]))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FamilyResultSig)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe InjectivityAnn)))))) 

data TySynEqn Source

One equation of a type family instance or closed type family. The arguments are the left-hand-side type patterns and the right-hand-side result.

Constructors

TySynEqn [Type] Type 

Instances

Eq TySynEqn 
Data TySynEqn 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TySynEqn -> c TySynEqn Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TySynEqn Source

toConstr :: TySynEqn -> Constr Source

dataTypeOf :: TySynEqn -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TySynEqn) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TySynEqn) Source

gmapT :: (forall b. Data b => b -> b) -> TySynEqn -> TySynEqn Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TySynEqn -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TySynEqn -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TySynEqn -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TySynEqn -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn Source

Ord TySynEqn 
Show TySynEqn 
Generic TySynEqn 

Associated Types

type Rep TySynEqn :: * -> * Source

type Rep TySynEqn = D1 (MetaData "TySynEqn" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "TySynEqn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))) 

data FunDep Source

Constructors

FunDep [Name] [Name] 

Instances

Eq FunDep 

Methods

(==) :: FunDep -> FunDep -> Bool

(/=) :: FunDep -> FunDep -> Bool

Data FunDep 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep -> c FunDep Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunDep Source

toConstr :: FunDep -> Constr Source

dataTypeOf :: FunDep -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c FunDep) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunDep) Source

gmapT :: (forall b. Data b => b -> b) -> FunDep -> FunDep Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FunDep -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source

Ord FunDep 
Show FunDep 
Generic FunDep 

Associated Types

type Rep FunDep :: * -> * Source

Ppr FunDep 
type Rep FunDep = D1 (MetaData "FunDep" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "FunDep" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])))) 

data FamFlavour Source

Constructors

TypeFam 
DataFam 

Instances

Eq FamFlavour 
Data FamFlavour 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamFlavour -> c FamFlavour Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FamFlavour Source

toConstr :: FamFlavour -> Constr Source

dataTypeOf :: FamFlavour -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c FamFlavour) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FamFlavour) Source

gmapT :: (forall b. Data b => b -> b) -> FamFlavour -> FamFlavour Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamFlavour -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamFlavour -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FamFlavour -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamFlavour -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamFlavour -> m FamFlavour Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamFlavour -> m FamFlavour Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamFlavour -> m FamFlavour Source

Ord FamFlavour 
Show FamFlavour 
Generic FamFlavour 

Associated Types

type Rep FamFlavour :: * -> * Source

Ppr FamFlavour 
type Rep FamFlavour = D1 (MetaData "FamFlavour" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "TypeFam" PrefixI False) U1) (C1 (MetaCons "DataFam" PrefixI False) U1)) 

data Foreign Source

Instances

Eq Foreign 

Methods

(==) :: Foreign -> Foreign -> Bool

(/=) :: Foreign -> Foreign -> Bool

Data Foreign 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Foreign -> c Foreign Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Foreign Source

toConstr :: Foreign -> Constr Source

dataTypeOf :: Foreign -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Foreign) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Foreign) Source

gmapT :: (forall b. Data b => b -> b) -> Foreign -> Foreign Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Foreign -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Foreign -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Foreign -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Foreign -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign Source

Ord Foreign 
Show Foreign 
Generic Foreign 

Associated Types

type Rep Foreign :: * -> * Source

Ppr Foreign 
type Rep Foreign = D1 (MetaData "Foreign" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "ImportF" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Callconv)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Safety))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) (C1 (MetaCons "ExportF" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Callconv)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) 

data Callconv Source

Constructors

CCall 
StdCall 
CApi 
Prim 
JavaScript 

Instances

Eq Callconv 
Data Callconv 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Callconv -> c Callconv Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Callconv Source

toConstr :: Callconv -> Constr Source

dataTypeOf :: Callconv -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Callconv) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callconv) Source

gmapT :: (forall b. Data b => b -> b) -> Callconv -> Callconv Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Callconv -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Callconv -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source

Ord Callconv 
Show Callconv 
Generic Callconv 

Associated Types

type Rep Callconv :: * -> * Source

type Rep Callconv = D1 (MetaData "Callconv" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "CCall" PrefixI False) U1) (C1 (MetaCons "StdCall" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CApi" PrefixI False) U1) ((:+:) (C1 (MetaCons "Prim" PrefixI False) U1) (C1 (MetaCons "JavaScript" PrefixI False) U1)))) 

data Safety Source

Constructors

Unsafe 
Safe 
Interruptible 

Instances

Eq Safety 

Methods

(==) :: Safety -> Safety -> Bool

(/=) :: Safety -> Safety -> Bool

Data Safety 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety -> c Safety Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Safety Source

toConstr :: Safety -> Constr Source

dataTypeOf :: Safety -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Safety) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Safety) Source

gmapT :: (forall b. Data b => b -> b) -> Safety -> Safety Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Safety -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source

Ord Safety 
Show Safety 
Generic Safety 

Associated Types

type Rep Safety :: * -> * Source

type Rep Safety = D1 (MetaData "Safety" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "Unsafe" PrefixI False) U1) ((:+:) (C1 (MetaCons "Safe" PrefixI False) U1) (C1 (MetaCons "Interruptible" PrefixI False) U1))) 

data Pragma Source

Instances

Eq Pragma 

Methods

(==) :: Pragma -> Pragma -> Bool

(/=) :: Pragma -> Pragma -> Bool

Data Pragma 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pragma -> c Pragma Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pragma Source

toConstr :: Pragma -> Constr Source

dataTypeOf :: Pragma -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Pragma) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pragma) Source

gmapT :: (forall b. Data b => b -> b) -> Pragma -> Pragma Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pragma -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pragma -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Pragma -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pragma -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma Source

Ord Pragma 
Show Pragma 
Generic Pragma 

Associated Types

type Rep Pragma :: * -> * Source

Ppr Pragma 
type Rep Pragma = D1 (MetaData "Pragma" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "InlineP" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Inline))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RuleMatch)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Phases))))) ((:+:) (C1 (MetaCons "SpecialiseP" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Inline))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Phases))))) (C1 (MetaCons "SpecialiseInstP" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) ((:+:) (C1 (MetaCons "RuleP" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RuleBndr]))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Phases)))))) ((:+:) (C1 (MetaCons "AnnP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnnTarget)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "LineP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))) 

data Inline Source

Constructors

NoInline 
Inline 
Inlinable 

Instances

Eq Inline 

Methods

(==) :: Inline -> Inline -> Bool

(/=) :: Inline -> Inline -> Bool

Data Inline 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline Source

toConstr :: Inline -> Constr Source

dataTypeOf :: Inline -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Inline) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) Source

gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Inline -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Inline -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source

Ord Inline 
Show Inline 
Generic Inline 

Associated Types

type Rep Inline :: * -> * Source

Ppr Inline 
type Rep Inline = D1 (MetaData "Inline" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NoInline" PrefixI False) U1) ((:+:) (C1 (MetaCons "Inline" PrefixI False) U1) (C1 (MetaCons "Inlinable" PrefixI False) U1))) 

data RuleMatch Source

Constructors

ConLike 
FunLike 

Instances

Eq RuleMatch 
Data RuleMatch 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatch -> c RuleMatch Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatch Source

toConstr :: RuleMatch -> Constr Source

dataTypeOf :: RuleMatch -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatch) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatch) Source

gmapT :: (forall b. Data b => b -> b) -> RuleMatch -> RuleMatch Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r Source

gmapQ :: (forall d. Data d => d -> u) -> RuleMatch -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatch -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source

Ord RuleMatch 
Show RuleMatch 
Generic RuleMatch 

Associated Types

type Rep RuleMatch :: * -> * Source

Ppr RuleMatch 
type Rep RuleMatch = D1 (MetaData "RuleMatch" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "ConLike" PrefixI False) U1) (C1 (MetaCons "FunLike" PrefixI False) U1)) 

data Phases Source

Instances

Eq Phases 

Methods

(==) :: Phases -> Phases -> Bool

(/=) :: Phases -> Phases -> Bool

Data Phases 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Phases -> c Phases Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Phases Source

toConstr :: Phases -> Constr Source

dataTypeOf :: Phases -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Phases) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Phases) Source

gmapT :: (forall b. Data b => b -> b) -> Phases -> Phases Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Phases -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Phases -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source

Ord Phases 
Show Phases 
Generic Phases 

Associated Types

type Rep Phases :: * -> * Source

Ppr Phases 
type Rep Phases = D1 (MetaData "Phases" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "AllPhases" PrefixI False) U1) ((:+:) (C1 (MetaCons "FromPhase" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) (C1 (MetaCons "BeforePhase" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) 

data RuleBndr Source

Instances

Eq RuleBndr 
Data RuleBndr 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr -> c RuleBndr Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleBndr Source

toConstr :: RuleBndr -> Constr Source

dataTypeOf :: RuleBndr -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c RuleBndr) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleBndr) Source

gmapT :: (forall b. Data b => b -> b) -> RuleBndr -> RuleBndr Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr -> r Source

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr Source

Ord RuleBndr 
Show RuleBndr 
Generic RuleBndr 

Associated Types

type Rep RuleBndr :: * -> * Source

Ppr RuleBndr 
type Rep RuleBndr = D1 (MetaData "RuleBndr" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "RuleVar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "TypedRuleVar" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) 

data AnnTarget Source

Instances

Eq AnnTarget 
Data AnnTarget 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnTarget -> c AnnTarget Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnTarget Source

toConstr :: AnnTarget -> Constr Source

dataTypeOf :: AnnTarget -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c AnnTarget) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnTarget) Source

gmapT :: (forall b. Data b => b -> b) -> AnnTarget -> AnnTarget Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r Source

gmapQ :: (forall d. Data d => d -> u) -> AnnTarget -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnTarget -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source

Ord AnnTarget 
Show AnnTarget 
Generic AnnTarget 

Associated Types

type Rep AnnTarget :: * -> * Source

type Rep AnnTarget = D1 (MetaData "AnnTarget" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "ModuleAnnotation" PrefixI False) U1) ((:+:) (C1 (MetaCons "TypeAnnotation" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "ValueAnnotation" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))))) 

type Cxt Source

Arguments

 = [Pred]
(Eq a, Ord b)

type Pred = Type Source

Since the advent of ConstraintKinds, constraints are really just types. Equality constraints use the EqualityT constructor. Constraints may also be tuples of other constraints.

data SourceUnpackedness Source

Constructors

NoSourceUnpackedness
C a
SourceNoUnpack
C { {-# NOUNPACK #-} } a
SourceUnpack
C { {-# UNPACK #-} } a

Instances

Eq SourceUnpackedness 
Data SourceUnpackedness 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceUnpackedness -> c SourceUnpackedness Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceUnpackedness Source

toConstr :: SourceUnpackedness -> Constr Source

dataTypeOf :: SourceUnpackedness -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c SourceUnpackedness) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceUnpackedness) Source

gmapT :: (forall b. Data b => b -> b) -> SourceUnpackedness -> SourceUnpackedness Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SourceUnpackedness -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceUnpackedness -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness Source

Ord SourceUnpackedness 
Show SourceUnpackedness 
Generic SourceUnpackedness 
Ppr SourceUnpackedness 
type Rep SourceUnpackedness = D1 (MetaData "SourceUnpackedness" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NoSourceUnpackedness" PrefixI False) U1) ((:+:) (C1 (MetaCons "SourceNoUnpack" PrefixI False) U1) (C1 (MetaCons "SourceUnpack" PrefixI False) U1))) 

data SourceStrictness Source

Constructors

NoSourceStrictness
C a
SourceLazy
C {~}a
SourceStrict
C {!}a

Instances

Eq SourceStrictness 
Data SourceStrictness 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceStrictness -> c SourceStrictness Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceStrictness Source

toConstr :: SourceStrictness -> Constr Source

dataTypeOf :: SourceStrictness -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c SourceStrictness) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceStrictness) Source

gmapT :: (forall b. Data b => b -> b) -> SourceStrictness -> SourceStrictness Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SourceStrictness -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceStrictness -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness Source

Ord SourceStrictness 
Show SourceStrictness 
Generic SourceStrictness 
Ppr SourceStrictness 
type Rep SourceStrictness = D1 (MetaData "SourceStrictness" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NoSourceStrictness" PrefixI False) U1) ((:+:) (C1 (MetaCons "SourceLazy" PrefixI False) U1) (C1 (MetaCons "SourceStrict" PrefixI False) U1))) 

data DecidedStrictness Source

Unlike SourceStrictness and SourceUnpackedness, DecidedStrictness refers to the strictness that the compiler chooses for a data constructor field, which may be different from what is written in source code. See reifyConStrictness for more information.

Instances

Eq DecidedStrictness 
Data DecidedStrictness 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecidedStrictness -> c DecidedStrictness Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecidedStrictness Source

toConstr :: DecidedStrictness -> Constr Source

dataTypeOf :: DecidedStrictness -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c DecidedStrictness) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecidedStrictness) Source

gmapT :: (forall b. Data b => b -> b) -> DecidedStrictness -> DecidedStrictness Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r Source

gmapQ :: (forall d. Data d => d -> u) -> DecidedStrictness -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> DecidedStrictness -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness Source

Ord DecidedStrictness 
Show DecidedStrictness 
Generic DecidedStrictness 
Ppr DecidedStrictness 
type Rep DecidedStrictness = D1 (MetaData "DecidedStrictness" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "DecidedLazy" PrefixI False) U1) ((:+:) (C1 (MetaCons "DecidedStrict" PrefixI False) U1) (C1 (MetaCons "DecidedUnpack" PrefixI False) U1))) 

data Con Source

Constructors

NormalC Name [BangType]
C Int a
RecC Name [VarBangType]
C { v :: Int, w :: a }
InfixC BangType Name BangType
Int :+ a
ForallC [TyVarBndr] Cxt Con
forall a. Eq a => C [a]
GadtC [Name] [BangType] Type
C :: a -> b -> T b Int
RecGadtC [Name] [VarBangType] Type
C :: { v :: Int } -> T b Int

Instances

Eq Con 

Methods

(==) :: Con -> Con -> Bool

(/=) :: Con -> Con -> Bool

Data Con 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Con -> c Con Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Con Source

toConstr :: Con -> Constr Source

dataTypeOf :: Con -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Con) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Con) Source

gmapT :: (forall b. Data b => b -> b) -> Con -> Con Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Con -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Con -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Con -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Con -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Con -> m Con Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Con -> m Con Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Con -> m Con Source

Ord Con 

Methods

compare :: Con -> Con -> Ordering

(<) :: Con -> Con -> Bool

(<=) :: Con -> Con -> Bool

(>) :: Con -> Con -> Bool

(>=) :: Con -> Con -> Bool

max :: Con -> Con -> Con

min :: Con -> Con -> Con

Show Con 
Generic Con 

Associated Types

type Rep Con :: * -> * Source

Methods

from :: Con -> Rep Con x Source

to :: Rep Con x -> Con Source

Ppr Con 

Methods

ppr :: Con -> Doc Source

ppr_list :: [Con] -> Doc Source

type Rep Con = D1 (MetaData "Con" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "NormalC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BangType])))) ((:+:) (C1 (MetaCons "RecC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VarBangType])))) (C1 (MetaCons "InfixC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BangType)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BangType))))))) ((:+:) (C1 (MetaCons "ForallC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Con))))) ((:+:) (C1 (MetaCons "GadtC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BangType])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) (C1 (MetaCons "RecGadtC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VarBangType])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))))) 

data Bang Source

Constructors

Bang SourceUnpackedness SourceStrictness
C { {-# UNPACK #-} !}a

Instances

Eq Bang 

Methods

(==) :: Bang -> Bang -> Bool

(/=) :: Bang -> Bang -> Bool

Data Bang 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bang -> c Bang Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bang Source

toConstr :: Bang -> Constr Source

dataTypeOf :: Bang -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Bang) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bang) Source

gmapT :: (forall b. Data b => b -> b) -> Bang -> Bang Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Bang -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bang -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source

Ord Bang 

Methods

compare :: Bang -> Bang -> Ordering

(<) :: Bang -> Bang -> Bool

(<=) :: Bang -> Bang -> Bool

(>) :: Bang -> Bang -> Bool

(>=) :: Bang -> Bang -> Bool

max :: Bang -> Bang -> Bang

min :: Bang -> Bang -> Bang

Show Bang 
Generic Bang 

Associated Types

type Rep Bang :: * -> * Source

Methods

from :: Bang -> Rep Bang x Source

to :: Rep Bang x -> Bang Source

Ppr Bang 

Methods

ppr :: Bang -> Doc Source

ppr_list :: [Bang] -> Doc Source

type Rep Bang = D1 (MetaData "Bang" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Bang" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceUnpackedness)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceStrictness)))) 

type Strict = Bang Source

As of template-haskell-2.11.0.0, Strict has been replaced by Bang.

type StrictType = BangType Source

As of template-haskell-2.11.0.0, StrictType has been replaced by BangType.

type VarStrictType = VarBangType Source

As of template-haskell-2.11.0.0, VarStrictType has been replaced by VarBangType.

data Type Source

Constructors

ForallT [TyVarBndr] Cxt Type
forall <vars>. <ctxt> -> <type>
AppT Type Type
T a b
SigT Type Kind
t :: k
VarT Name
a
ConT Name
T
PromotedT Name
'T
InfixT Type Name Type
T + T
UInfixT Type Name Type
T + T

See Language.Haskell.TH.Syntax

ParensT Type
(T)
TupleT Int
(,), (,,), etc.
UnboxedTupleT Int
(#,#), (#,,#), etc.
ArrowT
->
EqualityT
~
ListT
[]
PromotedTupleT Int
'(), '(,), '(,,), etc.
PromotedNilT
'[]
PromotedConsT
(':)
StarT
*
ConstraintT
Constraint
LitT TyLit
0,1,2, etc.
WildCardT

@_,

Instances

Eq Type 

Methods

(==) :: Type -> Type -> Bool

(/=) :: Type -> Type -> Bool

Data Type 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type Source

toConstr :: Type -> Constr Source

dataTypeOf :: Type -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Type) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) Source

gmapT :: (forall b. Data b => b -> b) -> Type -> Type Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source

Ord Type 

Methods

compare :: Type -> Type -> Ordering

(<) :: Type -> Type -> Bool

(<=) :: Type -> Type -> Bool

(>) :: Type -> Type -> Bool

(>=) :: Type -> Type -> Bool

max :: Type -> Type -> Type

min :: Type -> Type -> Type

Show Type 
Generic Type 

Associated Types

type Rep Type :: * -> * Source

Methods

from :: Type -> Rep Type x Source

to :: Rep Type x -> Type Source

Ppr Type 

Methods

ppr :: Type -> Doc Source

ppr_list :: [Type] -> Doc Source

type Rep Type = D1 (MetaData "Type" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ForallT" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) (C1 (MetaCons "AppT" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) ((:+:) (C1 (MetaCons "SigT" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind)))) ((:+:) (C1 (MetaCons "VarT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "ConT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))))) ((:+:) ((:+:) (C1 (MetaCons "PromotedT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "InfixT" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) ((:+:) (C1 (MetaCons "UInfixT" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) ((:+:) (C1 (MetaCons "ParensT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) (C1 (MetaCons "TupleT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UnboxedTupleT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) (C1 (MetaCons "ArrowT" PrefixI False) U1)) ((:+:) (C1 (MetaCons "EqualityT" PrefixI False) U1) ((:+:) (C1 (MetaCons "ListT" PrefixI False) U1) (C1 (MetaCons "PromotedTupleT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))))) ((:+:) ((:+:) (C1 (MetaCons "PromotedNilT" PrefixI False) U1) ((:+:) (C1 (MetaCons "PromotedConsT" PrefixI False) U1) (C1 (MetaCons "StarT" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ConstraintT" PrefixI False) U1) ((:+:) (C1 (MetaCons "LitT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TyLit))) (C1 (MetaCons "WildCardT" PrefixI False) U1)))))) 

data TyVarBndr Source

Constructors

PlainTV Name
a
KindedTV Name Kind
(a :: k)

Instances

Eq TyVarBndr 
Data TyVarBndr 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyVarBndr -> c TyVarBndr Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyVarBndr Source

toConstr :: TyVarBndr -> Constr Source

dataTypeOf :: TyVarBndr -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TyVarBndr) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyVarBndr) Source

gmapT :: (forall b. Data b => b -> b) -> TyVarBndr -> TyVarBndr Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TyVarBndr -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyVarBndr -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr Source

Ord TyVarBndr 
Show TyVarBndr 
Generic TyVarBndr 

Associated Types

type Rep TyVarBndr :: * -> * Source

Ppr TyVarBndr 
type Rep TyVarBndr = D1 (MetaData "TyVarBndr" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "PlainTV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) (C1 (MetaCons "KindedTV" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind))))) 

data FamilyResultSig Source

Type family result signature

Constructors

NoSig

no signature

KindSig Kind
k
TyVarSig TyVarBndr
= r, = (r :: k)

Instances

Eq FamilyResultSig 
Data FamilyResultSig 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig -> c FamilyResultSig Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FamilyResultSig Source

toConstr :: FamilyResultSig -> Constr Source

dataTypeOf :: FamilyResultSig -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c FamilyResultSig) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FamilyResultSig) Source

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig -> FamilyResultSig Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig Source

Ord FamilyResultSig 
Show FamilyResultSig 
Generic FamilyResultSig 
Ppr FamilyResultSig 
type Rep FamilyResultSig = D1 (MetaData "FamilyResultSig" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NoSig" PrefixI False) U1) ((:+:) (C1 (MetaCons "KindSig" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind))) (C1 (MetaCons "TyVarSig" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TyVarBndr))))) 

data InjectivityAnn Source

Injectivity annotation

Constructors

InjectivityAnn Name [Name] 

Instances

Eq InjectivityAnn 
Data InjectivityAnn 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn -> c InjectivityAnn Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InjectivityAnn Source

toConstr :: InjectivityAnn -> Constr Source

dataTypeOf :: InjectivityAnn -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c InjectivityAnn) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InjectivityAnn) Source

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn -> InjectivityAnn Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn -> r Source

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn Source

Ord InjectivityAnn 
Show InjectivityAnn 
Generic InjectivityAnn 
Ppr InjectivityAnn 
type Rep InjectivityAnn = D1 (MetaData "InjectivityAnn" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "InjectivityAnn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Name])))) 

data TyLit Source

Instances

Eq TyLit 

Methods

(==) :: TyLit -> TyLit -> Bool

(/=) :: TyLit -> TyLit -> Bool

Data TyLit 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyLit -> c TyLit Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyLit Source

toConstr :: TyLit -> Constr Source

dataTypeOf :: TyLit -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TyLit) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit) Source

gmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TyLit -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyLit -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source

Ord TyLit 

Methods

compare :: TyLit -> TyLit -> Ordering

(<) :: TyLit -> TyLit -> Bool

(<=) :: TyLit -> TyLit -> Bool

(>) :: TyLit -> TyLit -> Bool

(>=) :: TyLit -> TyLit -> Bool

max :: TyLit -> TyLit -> TyLit

min :: TyLit -> TyLit -> TyLit

Show TyLit 
Generic TyLit 

Associated Types

type Rep TyLit :: * -> * Source

Methods

from :: TyLit -> Rep TyLit x Source

to :: Rep TyLit x -> TyLit Source

Ppr TyLit 

Methods

ppr :: TyLit -> Doc Source

ppr_list :: [TyLit] -> Doc Source

type Rep TyLit = D1 (MetaData "TyLit" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "NumTyLit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "StrTyLit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) 

data Role Source

Role annotations

Constructors

NominalR
nominal
RepresentationalR
representational
PhantomR
phantom
InferR
_

Instances

Eq Role 

Methods

(==) :: Role -> Role -> Bool

(/=) :: Role -> Role -> Bool

Data Role 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role Source

toConstr :: Role -> Constr Source

dataTypeOf :: Role -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Role) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) Source

gmapT :: (forall b. Data b => b -> b) -> Role -> Role Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source

Ord Role 

Methods

compare :: Role -> Role -> Ordering

(<) :: Role -> Role -> Bool

(<=) :: Role -> Role -> Bool

(>) :: Role -> Role -> Bool

(>=) :: Role -> Role -> Bool

max :: Role -> Role -> Role

min :: Role -> Role -> Role

Show Role 
Generic Role 

Associated Types

type Rep Role :: * -> * Source

Methods

from :: Role -> Rep Role x Source

to :: Rep Role x -> Role Source

Ppr Role 

Methods

ppr :: Role -> Doc Source

ppr_list :: [Role] -> Doc Source

type Rep Role = D1 (MetaData "Role" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) ((:+:) (C1 (MetaCons "NominalR" PrefixI False) U1) (C1 (MetaCons "RepresentationalR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PhantomR" PrefixI False) U1) (C1 (MetaCons "InferR" PrefixI False) U1))) 

data AnnLookup Source

Annotation target for reifyAnnotations

Instances

Eq AnnLookup 
Data AnnLookup 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnLookup -> c AnnLookup Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnLookup Source

toConstr :: AnnLookup -> Constr Source

dataTypeOf :: AnnLookup -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c AnnLookup) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnLookup) Source

gmapT :: (forall b. Data b => b -> b) -> AnnLookup -> AnnLookup Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r Source

gmapQ :: (forall d. Data d => d -> u) -> AnnLookup -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnLookup -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source

Ord AnnLookup 
Show AnnLookup 
Generic AnnLookup 

Associated Types

type Rep AnnLookup :: * -> * Source

type Rep AnnLookup = D1 (MetaData "AnnLookup" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) (C1 (MetaCons "AnnLookupModule" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Module))) (C1 (MetaCons "AnnLookupName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))) 

type Kind = Type Source

To avoid duplication between kinds and types, they are defined to be the same. Naturally, you would never have a type be StarT and you would never have a kind be SigT, but many of the other constructors are shared. Note that the kind Bool is denoted with ConT, not PromotedT. Similarly, tuple kinds are made with TupleT, not PromotedTupleT.

Language extensions