functor-friends-0.1.0.0: Friendly helpers for your recursion schemes.

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Tutorial

Synopsis

Documentation

data AstF t Source #

An example AST type, as an F-algebra. This AST will be used to demonstrate some tricks for composing new data types while maintaining separation of concerns.

This approach was inspired by the recursion-schemes library and the "Data Types a la Carte" paper.

Constructors

RealF Double 
ComplexF Double Double 
VarF String 
AddF t t 
MulF t t 
AbsF t 

Instances

Functor AstF Source # 

Methods

fmap :: (a -> b) -> AstF a -> AstF b #

(<$) :: a -> AstF b -> AstF a #

Eq t => Eq (AstF t) Source # 

Methods

(==) :: AstF t -> AstF t -> Bool #

(/=) :: AstF t -> AstF t -> Bool #

Ord t => Ord (AstF t) Source # 

Methods

compare :: AstF t -> AstF t -> Ordering #

(<) :: AstF t -> AstF t -> Bool #

(<=) :: AstF t -> AstF t -> Bool #

(>) :: AstF t -> AstF t -> Bool #

(>=) :: AstF t -> AstF t -> Bool #

max :: AstF t -> AstF t -> AstF t #

min :: AstF t -> AstF t -> AstF t #

Pretty t => Pretty (AstF t) Source #

Pretty-printer for ASTs.

Methods

pretty :: AstF t -> String Source #

pattern Add :: Fix AstF -> Fix AstF -> Fix AstF Source #

Patterns to simplify the construction and destructuring of ASTs

pattern Mul :: Fix AstF -> Fix AstF -> Fix AstF Source #

pattern Abs :: Fix AstF -> Fix AstF Source #

pattern Real :: Double -> Fix AstF Source #

pattern Complex :: Double -> Double -> Fix AstF Source #

pattern Var :: String -> Fix AstF Source #

class Pretty a where Source #

A pretty-printing typeclass.

This demonstrates an approach to separation of concerns; the pretty-printer for normal ASTs is implemented independently from the pretty-printer for holes and the pretty-printer for annotations.

Although the implementations don't know about each other, they can still be composed; as a result, a Holey Ast knows how to print itself using a mixture of the pretty-printer for Asts and the pretty-printer for Holes.

Minimal complete definition

pretty

Methods

pretty :: a -> String Source #

Instances

Pretty (f (Fix f)) => Pretty (Fix f) Source #

Pretty-printer for fixpoints.

Methods

pretty :: Fix f -> String Source #

Pretty t => Pretty (AstF t) Source #

Pretty-printer for ASTs.

Methods

pretty :: AstF t -> String Source #

Pretty (f (Fix (HoleF f))) => Pretty (HoleF f (Fix (HoleF f))) Source #

Pretty-printer for holes.

Methods

pretty :: HoleF f (Fix (HoleF f)) -> String Source #

(Pretty (f (Fix (AnnotatedF a f))), Show a) => Pretty (AnnotatedF a f (Fix (AnnotatedF a f))) Source #

Pretty-printer for annotations.

Methods

pretty :: AnnotatedF a f (Fix (AnnotatedF a f)) -> String Source #

expr1 :: Ast Source #

A simple expression

expr2 :: Ast Source #

Another simple expression

expr3 :: Holey Ast Source #

An expression-with-holes. Holes can be plugged with plug.

λ> pretty expr3 "|(_ + 1.0)|"

λ> pretty (plug (Var "z") expr3) "|(z + 1.0)|"

λ> :t plug (Var "z") expr3 plug (Var "z") expr3 :: Fix AstF -- aka Ast

data Type Source #

Real and Complex type tags

Constructors

R 
C 

Instances

Eq Type Source # 

Methods

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

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

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

inferTypes :: Ast -> Annotated Type Ast Source #

Annotate each subexpression with its type (real or complex).

λ> pretty expr1 "|((2.0 * (0.0 + 1.0i)) + 1.0)|"

λ> pretty (inferTypes expr1) "|((2.0{R} * (0.0 + 1.0i){C}){C} + 1.0{R}){C}|{R}"

unreal :: Ast -> Holey Ast Source #

Remove all real-valued subexpressions, leaving a Hole in their place.

λ> pretty expr2 "((z * z) + (3.0 * z))"

λ> pretty (unreal expr2) "((z * z) + (_ * z))"