Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
The core types of Fixplate.
Synopsis
- newtype Mu f = Fix {}
- isAtom :: Foldable f => Mu f -> Bool
- data Ann f a b = Ann {}
- type Attr f a = Mu (Ann f a)
- liftAnn :: (f e -> g e) -> Ann f a e -> Ann g a e
- data CoAnn f a b
- type CoAttr f a = Mu (CoAnn f a)
- liftCoAnn :: (f e -> g e) -> CoAnn f a e -> CoAnn g a e
- attribute :: Attr f a -> a
- forget :: Functor f => Attr f a -> Mu f
- data Hole = Hole
- class EqF f where
- class EqF f => OrdF f where
- class ShowF f where
- showsPrecF :: Show a => Int -> f a -> ShowS
- class ReadF f where
- showF :: (ShowF f, Show a) => f a -> String
- showsF :: (ShowF f, Show a) => f a -> ShowS
- newtype Attrib f a = Attrib {}
- newtype CoAttrib f a = CoAttrib {
- unCoAttrib :: CoAttr f a
Documentation
The fixed-point type.
Annotations
Type of annotations
Instances
Functor f => Functor (Ann f a) Source # | |
Foldable f => Foldable (Ann f a) Source # | |
Defined in Data.Generics.Fixplate.Base fold :: Monoid m => Ann f a m -> m # foldMap :: Monoid m => (a0 -> m) -> Ann f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Ann f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Ann f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Ann f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Ann f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Ann f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Ann f a a0 -> a0 # toList :: Ann f a a0 -> [a0] # elem :: Eq a0 => a0 -> Ann f a a0 -> Bool # maximum :: Ord a0 => Ann f a a0 -> a0 # minimum :: Ord a0 => Ann f a a0 -> a0 # | |
Traversable f => Traversable (Ann f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Read a, ReadF f) => ReadF (Ann f a) Source # | |
(Show a, ShowF f) => ShowF (Ann f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Ord a, OrdF f) => OrdF (Ann f a) Source # | NOTE: The |
(Eq a, EqF f) => EqF (Ann f a) Source # | NOTE: The |
(Eq a, Eq (f b)) => Eq (Ann f a b) Source # | |
(Ord a, Ord (f b)) => Ord (Ann f a b) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Show a, Show (f b)) => Show (Ann f a b) Source # | |
liftAnn :: (f e -> g e) -> Ann f a e -> Ann g a e Source #
Lifting natural transformations to annotations.
Co-annotations
Categorical dual of Ann
.
Instances
Functor f => Functor (CoAnn f a) Source # | |
Foldable f => Foldable (CoAnn f a) Source # | |
Defined in Data.Generics.Fixplate.Base fold :: Monoid m => CoAnn f a m -> m # foldMap :: Monoid m => (a0 -> m) -> CoAnn f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> CoAnn f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> CoAnn f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> CoAnn f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> CoAnn f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> CoAnn f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> CoAnn f a a0 -> a0 # toList :: CoAnn f a a0 -> [a0] # null :: CoAnn f a a0 -> Bool # length :: CoAnn f a a0 -> Int # elem :: Eq a0 => a0 -> CoAnn f a a0 -> Bool # maximum :: Ord a0 => CoAnn f a a0 -> a0 # minimum :: Ord a0 => CoAnn f a a0 -> a0 # | |
Traversable f => Traversable (CoAnn f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Show a, ShowF f) => ShowF (CoAnn f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Ord a, OrdF f) => OrdF (CoAnn f a) Source # | |
(Eq a, EqF f) => EqF (CoAnn f a) Source # | |
(Eq a, Eq (f b)) => Eq (CoAnn f a b) Source # | |
(Ord a, Ord (f b)) => Ord (CoAnn f a b) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Show a, Show (f b)) => Show (CoAnn f a b) Source # | |
liftCoAnn :: (f e -> g e) -> CoAnn f a e -> CoAnn g a e Source #
Lifting natural transformations to annotations.
Annotated trees
forget :: Functor f => Attr f a -> Mu f Source #
A function forgetting all the attributes from an annotated tree.
Holes
This a data type defined to be a place-holder for childs.
It is used in tree drawing, hashing, and Shape
.
It is deliberately not made an instance of Show
, so that
you can choose your preferred style. For example, an acceptable choice is
instance Show Hole where show _ = "_"
Higher-order type classes
"Functorised" versions of standard type classes. If you have your a structure functor, for example
Expr e = Kst Int | Var String | Add e e deriving (Eq,Ord,Read,Show,Functor,Foldable,Traversable)
you should make it an instance of these, so that the
fixed-point type Mu Expr
can be an instance of
Eq
, Ord
and Show
. Doing so is very easy:
instance EqF Expr where equalF = (==) instance OrdF Expr where compareF = compare instance ShowF Expr where showsPrecF = showsPrec
The Read
instance depends on whether we are using GHC or not.
The Haskell98 version is
instance ReadF Expr where readsPrecF = readsPrec
while the GHC version is
instance ReadF Expr where readPrecF = readPrec
Instances
(Eq a, EqF f) => EqF (CoAnn f a) Source # | |
(Eq a, EqF f) => EqF (Ann f a) Source # | NOTE: The |
(Eq hash, EqF f) => EqF (HashAnn hash f) Source # | |
(EqF f, EqF g) => EqF (f :*: g) Source # | |
(EqF f, EqF g) => EqF (f :+: g) Source # | |
class EqF f => OrdF f where Source #
Instances
(Ord a, OrdF f) => OrdF (CoAnn f a) Source # | |
(Ord a, OrdF f) => OrdF (Ann f a) Source # | NOTE: The |
(Ord hash, OrdF f) => OrdF (HashAnn hash f) Source # | |
(OrdF f, OrdF g) => OrdF (f :*: g) Source # | |
(OrdF f, OrdF g) => OrdF (f :+: g) Source # | |
Instances
(Show a, ShowF f) => ShowF (CoAnn f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(Show a, ShowF f) => ShowF (Ann f a) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(ShowF f, Show hash) => ShowF (HashAnn hash f) Source # | |
Defined in Data.Generics.Fixplate.Hash | |
(ShowF f, ShowF g) => ShowF (f :*: g) Source # | |
Defined in Data.Generics.Fixplate.Functor | |
(ShowF f, ShowF g) => ShowF (f :+: g) Source # | |
Defined in Data.Generics.Fixplate.Functor |
Attrib (cofree comonad)
A newtype wrapper around Attr f a
so that we can make Attr f
an instance of Functor, Foldable and Traversable (and Comonad). This is necessary
since Haskell does not allow partial application of type synonyms.
Equivalent to the co-free comonad.
Instances
Functor f => Functor (Attrib f) Source # | |
Foldable f => Foldable (Attrib f) Source # | |
Defined in Data.Generics.Fixplate.Base fold :: Monoid m => Attrib f m -> m # foldMap :: Monoid m => (a -> m) -> Attrib f a -> m # foldr :: (a -> b -> b) -> b -> Attrib f a -> b # foldr' :: (a -> b -> b) -> b -> Attrib f a -> b # foldl :: (b -> a -> b) -> b -> Attrib f a -> b # foldl' :: (b -> a -> b) -> b -> Attrib f a -> b # foldr1 :: (a -> a -> a) -> Attrib f a -> a # foldl1 :: (a -> a -> a) -> Attrib f a -> a # elem :: Eq a => a -> Attrib f a -> Bool # maximum :: Ord a => Attrib f a -> a # minimum :: Ord a => Attrib f a -> a # | |
Traversable f => Traversable (Attrib f) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(ShowF f, Show a) => Show (Attrib f a) Source # | |
CoAttrib (free monad)
Categorial dual of Attrib
. Equivalent to the free monad.
CoAttrib | |
|
Instances
Functor f => Monad (CoAttrib f) Source # | |
Functor f => Functor (CoAttrib f) Source # | |
Functor f => Applicative (CoAttrib f) Source # | |
Defined in Data.Generics.Fixplate.Base | |
Foldable f => Foldable (CoAttrib f) Source # | |
Defined in Data.Generics.Fixplate.Base fold :: Monoid m => CoAttrib f m -> m # foldMap :: Monoid m => (a -> m) -> CoAttrib f a -> m # foldr :: (a -> b -> b) -> b -> CoAttrib f a -> b # foldr' :: (a -> b -> b) -> b -> CoAttrib f a -> b # foldl :: (b -> a -> b) -> b -> CoAttrib f a -> b # foldl' :: (b -> a -> b) -> b -> CoAttrib f a -> b # foldr1 :: (a -> a -> a) -> CoAttrib f a -> a # foldl1 :: (a -> a -> a) -> CoAttrib f a -> a # toList :: CoAttrib f a -> [a] # null :: CoAttrib f a -> Bool # length :: CoAttrib f a -> Int # elem :: Eq a => a -> CoAttrib f a -> Bool # maximum :: Ord a => CoAttrib f a -> a # minimum :: Ord a => CoAttrib f a -> a # | |
Traversable f => Traversable (CoAttrib f) Source # | |
Defined in Data.Generics.Fixplate.Base | |
(ShowF f, Show a) => Show (CoAttrib f a) Source # | |