tip-lib-0.1.2: tons of inductive problems - support library and tools

Safe HaskellSafe-Inferred
LanguageHaskell2010

Tip.Haskell.Repr

Description

A representation of Haskell programs

Documentation

data Decls a Source

Constructors

Decls [Decl a] 

Instances

data Decl a Source

Constructors

TySig a [Type a] (Type a) 
FunDecl a [([Pat a], Expr a)] 
DataDecl a [a] [(a, [Type a])] [a] 
InstDecl [Type a] (Type a) [Decl a] 
TypeDef (Type a) (Type a) 
(Decl a) `Where` [Decl a] 
TH (Expr a) 
Module String 
LANGUAGE String 
QualImport String (Maybe String) 

Instances

Functor Decl 
Foldable Decl 
Traversable Decl 
Eq a => Eq (Decl a) 
Ord a => Ord (Decl a) 
Show a => Show (Decl a) 
PrettyHsVar a => Pretty (Decl a) 

funDecl :: a -> [a] -> Expr a -> Decl a Source

data Type a Source

Constructors

TyCon a [Type a] 
TyVar a 
TyTup [Type a] 
TyArr (Type a) (Type a) 
TyForall [a] (Type a) 
TyCtx [Type a] (Type a) 
TyImp a (Type a) 

Instances

Functor Type 
Foldable Type 
Traversable Type 
Eq a => Eq (Type a) 
Ord a => Ord (Type a) 
Show a => Show (Type a) 
PrettyHsVar a => Pretty (Type a) 

modTyCon :: (a -> a) -> Type a -> Type a Source

data Expr a Source

Constructors

Apply a [Expr a] 
ImpVar a 
Do [Stmt a] (Expr a) 
Lam [Pat a] (Expr a) 
Let a (Expr a) (Expr a) 
ImpLet a (Expr a) (Expr a) 
List [Expr a] 
Tup [Expr a] 
String a 
Noop 
Case (Expr a) [(Pat a, Expr a)]
return ()
Int Integer 
QuoteTyCon a 
QuoteName a 
THSplice (Expr a) 
Record (Expr a) [(a, Expr a)] 
(Expr a) ::: (Type a) 

Instances

Functor Expr 
Foldable Expr 
Traversable Expr 
Eq a => Eq (Expr a) 
Ord a => Ord (Expr a) 
Show a => Show (Expr a) 
PrettyHsVar a => Pretty (Expr a) 

mkDo :: [Stmt t] -> Expr t -> Expr t Source

var :: a -> Expr a Source

data Pat a Source

Constructors

VarPat a 
ConPat a [Pat a] 
TupPat [Pat a] 
WildPat 
IntPat Integer 

Instances

Functor Pat 
Foldable Pat 
Traversable Pat 
Eq a => Eq (Pat a) 
Ord a => Ord (Pat a) 
Show a => Show (Pat a) 
PrettyHsVar a => Pretty (Pat a) 

data Stmt a Source

Constructors

Bind a (Expr a) 
BindTyped a (Type a) (Expr a) 
Stmt (Expr a) 

Instances

Functor Stmt 
Foldable Stmt 
Traversable Stmt 
Eq a => Eq (Stmt a) 
Ord a => Ord (Stmt a) 
Show a => Show (Stmt a) 
PrettyHsVar a => Pretty (Stmt a)