haskell-src-meta-0.8.0.2: Parse source to template-haskell abstract syntax.

Copyright(c) Matt Morrow 2008
LicenseBSD3
MaintainerMatt Morrow <mjm2002@gmail.com>
Stabilityexperimental
Portabilityportable (template-haskell)
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Meta.Syntax.Translate

Contents

Description

 

Synopsis

Documentation

class ToName a where Source #

Minimal complete definition

toName

Methods

toName :: a -> Name Source #

class ToNames a where Source #

Minimal complete definition

toNames

Methods

toNames :: a -> [Name] Source #

Instances

ToNames a => ToNames (Maybe a) Source # 

Methods

toNames :: Maybe a -> [Name] Source #

ToNames (InstRule l) Source # 

Methods

toNames :: InstRule l -> [Name] Source #

ToNames (InstHead l) Source # 

Methods

toNames :: InstHead l -> [Name] Source #

ToNames (Deriving l) Source # 

Methods

toNames :: Deriving l -> [Name] Source #

class ToLit a where Source #

Minimal complete definition

toLit

Methods

toLit :: a -> Lit Source #

class ToType a where Source #

Minimal complete definition

toType

Methods

toType :: a -> Type Source #

Instances

ToType (QName l) Source # 

Methods

toType :: QName l -> Type Source #

ToType (InstRule l) Source # 

Methods

toType :: InstRule l -> Type Source #

ToType (InstHead l) Source # 

Methods

toType :: InstHead l -> Type Source #

ToType (Type l) Source # 

Methods

toType :: Type l -> Type Source #

ToType (Kind l) Source # 

Methods

toType :: Kind l -> Type Source #

class ToPat a where Source #

Minimal complete definition

toPat

Methods

toPat :: a -> Pat Source #

Instances

ToPat Lit Source # 

Methods

toPat :: Lit -> Pat Source #

ToPat a => ToPat [a] Source # 

Methods

toPat :: [a] -> Pat Source #

ToPat (Pat l) Source # 

Methods

toPat :: Pat l -> Pat Source #

(ToPat a, ToPat b) => ToPat (a, b) Source # 

Methods

toPat :: (a, b) -> Pat Source #

(ToPat a, ToPat b, ToPat c) => ToPat (a, b, c) Source # 

Methods

toPat :: (a, b, c) -> Pat Source #

(ToPat a, ToPat b, ToPat c, ToPat d) => ToPat (a, b, c, d) Source # 

Methods

toPat :: (a, b, c, d) -> Pat Source #

class ToExp a where Source #

Minimal complete definition

toExp

Methods

toExp :: a -> Exp Source #

Instances

ToExp Lit Source # 

Methods

toExp :: Lit -> Exp Source #

ToExp a => ToExp [a] Source # 

Methods

toExp :: [a] -> Exp Source #

ToExp (QOp l) Source # 

Methods

toExp :: QOp l -> Exp Source #

ToExp (Exp l) Source # 

Methods

toExp :: Exp l -> Exp Source #

(ToExp a, ToExp b) => ToExp (a, b) Source # 

Methods

toExp :: (a, b) -> Exp Source #

(ToExp a, ToExp b, ToExp c) => ToExp (a, b, c) Source # 

Methods

toExp :: (a, b, c) -> Exp Source #

(ToExp a, ToExp b, ToExp c, ToExp d) => ToExp (a, b, c, d) Source # 

Methods

toExp :: (a, b, c, d) -> Exp Source #

class ToDecs a where Source #

Minimal complete definition

toDecs

Methods

toDecs :: a -> [Dec] Source #

Instances

ToDecs a => ToDecs [a] Source # 

Methods

toDecs :: [a] -> [Dec] Source #

ToDecs a => ToDecs (Maybe a) Source # 

Methods

toDecs :: Maybe a -> [Dec] Source #

ToDecs (Decl l) Source # 

Methods

toDecs :: Decl l -> [Dec] Source #

ToDecs (Binds l) Source # 

Methods

toDecs :: Binds l -> [Dec] Source #

ToDecs (ClassDecl l) Source # 

Methods

toDecs :: ClassDecl l -> [Dec] Source #

ToDecs (InstDecl l) Source # 

Methods

toDecs :: InstDecl l -> [Dec] Source #

class ToDec a where Source #

Minimal complete definition

toDec

Methods

toDec :: a -> Dec Source #

Instances

ToDec (Decl l) Source # 

Methods

toDec :: Decl l -> Dec Source #

class ToStmt a where Source #

Minimal complete definition

toStmt

Methods

toStmt :: a -> Stmt Source #

Instances

ToStmt (Stmt l) Source # 

Methods

toStmt :: Stmt l -> Stmt Source #

class ToLoc a where Source #

Minimal complete definition

toLoc

Methods

toLoc :: a -> Loc Source #

Instances

class ToCxt a where Source #

Minimal complete definition

toCxt

Methods

toCxt :: a -> Cxt Source #

Instances

ToCxt a => ToCxt (Maybe a) Source # 

Methods

toCxt :: Maybe a -> Cxt Source #

ToCxt (InstRule l) Source # 

Methods

toCxt :: InstRule l -> Cxt Source #

ToCxt (Context l) Source # 

Methods

toCxt :: Context l -> Cxt Source #

class ToPred a where Source #

Minimal complete definition

toPred

Methods

toPred :: a -> Pred Source #

Instances

ToPred (Asst l) Source # 

Methods

toPred :: Asst l -> Pred Source #

class ToTyVars a where Source #

Minimal complete definition

toTyVars

Methods

toTyVars :: a -> [TyVarBndr] Source #

Instances

class ToMaybeKind a where Source #

Minimal complete definition

toMaybeKind

Methods

toMaybeKind :: a -> Maybe Kind Source #

noTH :: (Functor f, Show (f ())) => String -> f e -> a Source #

noTHyet :: (Functor f, Show (f ())) => String -> String -> f e -> a Source #

todo :: (Functor f, Show (f ())) => String -> f e -> a Source #

nonsense :: (Functor f, Show (f ())) => String -> String -> f e -> a Source #

ToName {String,HsName,Module,HsSpecialCon,HsQName}

ToLit HsLiteral

ToPat HsPat

ToExp HsExp

ToLoc SrcLoc

ToType HsType

ToStmt HsStmt

ToDec HsDecl

ToDecs InstDecl

ToDecs HsDecl HsBinds