rewriting-0.1: Generic rewriting library for regular datatypes.Source codeContentsIndex
Generics.Regular.Rewriting.Base
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Functorial map function.
Monadic functorial map function.
Crush functions.
Zip functions.
Equality function.
Show function.
Functions for generating values that are different on top-level.
Description
Summary: Base generic functions that are used for generic rewriting.
Synopsis
Functor (fmap)
class GMap f where
fmapM :: Monad m => (a -> m b) -> f a -> m (f b)
class Crush f where
crush :: (a -> b -> b) -> b -> f a -> b
flatten :: Crush f => f a -> [a]
class Zip f where
fzipM :: Monad m => (a -> b -> m c) -> f a -> f b -> m (f c)
fzip :: (Zip f, Monad m) => (a -> b -> c) -> f a -> f b -> m (f c)
fzip' :: Zip f => (a -> b -> c) -> f a -> f b -> f c
geq :: (b ~ PF a, Regular a, Crush b, Zip b) => a -> a -> Bool
class GShow f where
gshow :: (a -> ShowS) -> f a -> ShowS
class LRBase a where
leftb :: a
rightb :: a
class LR f where
leftf :: a -> f a
rightf :: a -> f a
left :: (Regular a, LR (PF a)) => a
right :: (Regular a, LR (PF a)) => a
Functorial map function.
Functor (fmap)
Monadic functorial map function.
class GMap f whereSource
The GMap class defines a monadic functorial map.
Methods
fmapM :: Monad m => (a -> m b) -> f a -> m (f b)Source
show/hide Instances
GMap Unit
GMap Id
GMap f => GMap (Con f)
GMap (K a)
(GMap f, GMap g) => GMap (f :*: g)
(GMap f, GMap g) => GMap (f :+: g)
Crush functions.
class Crush f whereSource
The Crush class defines a crush on functorial values. In fact, crush is a generalized foldr.
Methods
crush :: (a -> b -> b) -> b -> f a -> bSource
show/hide Instances
Crush Unit
Crush Id
Crush f => Crush (Con f)
Crush (K a)
(Crush f, Crush g) => Crush (f :*: g)
(Crush f, Crush g) => Crush (f :+: g)
flatten :: Crush f => f a -> [a]Source
Flatten a structure by collecting all the elements present.
Zip functions.
class Zip f whereSource
The Zip class defines a monadic zip on functorial values.
Methods
fzipM :: Monad m => (a -> b -> m c) -> f a -> f b -> m (f c)Source
show/hide Instances
Zip Unit
Zip Id
Zip f => Zip (Con f)
Eq a => Zip (K a)
(Zip f, Zip g) => Zip (f :*: g)
(Zip f, Zip g) => Zip (f :+: g)
fzip :: (Zip f, Monad m) => (a -> b -> c) -> f a -> f b -> m (f c)Source
Functorial zip with a non-monadic function, resulting in a monadic value.
fzip' :: Zip f => (a -> b -> c) -> f a -> f b -> f cSource
Partial functorial zip with a non-monadic function.
Equality function.
geq :: (b ~ PF a, Regular a, Crush b, Zip b) => a -> a -> BoolSource
Equality on values based on their structural representation.
Show function.
class GShow f whereSource
The GShow class defines a show on values.
Methods
gshow :: (a -> ShowS) -> f a -> ShowSSource
show/hide Instances
GShow Unit
GShow Id
GShow f => GShow (Con f)
Show a => GShow (K a)
(GShow f, GShow g) => GShow (f :*: g)
(GShow f, GShow g) => GShow (f :+: g)
Functions for generating values that are different on top-level.
class LRBase a whereSource
The LRBase class defines two functions, leftb and rightb, which should produce different values.
Methods
leftb :: aSource
rightb :: aSource
show/hide Instances
class LR f whereSource
The LR class defines two functions, leftf and rightf, which should produce different functorial values.
Methods
leftf :: a -> f aSource
rightf :: a -> f aSource
show/hide Instances
LR Unit
LR Id
LR f => LR (Con f)
LRBase a => LR (K a)
(LR f, LR g) => LR (f :*: g)
(LR f, LR g) => LR (f :+: g)
left :: (Regular a, LR (PF a)) => aSource
Produces a value which should be different from the value returned by right.
right :: (Regular a, LR (PF a)) => aSource
Produces a value which should be different from the value returned by left.
Produced by Haddock version 2.4.2