regular-0.1: Generic programming library for regular datatypes.Source codeContentsIndex
Generics.Regular.Functions
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Functorial map function
Monadic functorial map function
Crush right functions
Zip functions
Equality function
Show function
Functions for generating values that are different on top-level
Generic folding
Description
Summary: Generic functionality for regular dataypes: mapM, flatten, zip, equality, show, value generation and fold.
Synopsis
Functor (fmap)
class GMap f where
fmapM :: Monad m => (a -> m b) -> f a -> m (f b)
class CrushR f where
crushr :: (a -> b -> b) -> b -> f a -> b
flatten :: CrushR 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, CrushR b, Zip b) => a -> a -> Bool
class GShow f where
gshowf :: (a -> ShowS) -> f a -> ShowS
gshow :: (Regular a, GShow (PF a)) => 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
type family Alg f r :: *
type Algebra a r = Alg (PF a) r
class Fold f where
alg :: Alg f r -> f r -> r
fold :: (Regular a, Fold (PF a), Functor (PF a)) => Algebra a r -> a -> r
(&) :: a -> b -> (a, b)
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 U
GMap I
GMap (K a)
GMap f => GMap (C c f)
(GMap f, GMap g) => GMap (f :*: g)
(GMap f, GMap g) => GMap (f :+: g)
Crush right functions
class CrushR f whereSource
The CrushR class defines a right-associative crush on functorial values.
Methods
crushr :: (a -> b -> b) -> b -> f a -> bSource
show/hide Instances
CrushR U
CrushR I
CrushR (K a)
CrushR f => CrushR (C c f)
(CrushR f, CrushR g) => CrushR (f :*: g)
(CrushR f, CrushR g) => CrushR (f :+: g)
flatten :: CrushR 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 U
Zip I
Eq a => Zip (K a)
Zip f => Zip (C c f)
(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, CrushR 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
gshowf :: (a -> ShowS) -> f a -> ShowSSource
show/hide Instances
GShow U
GShow I
Show a => GShow (K a)
(Constructor c, GShow f) => GShow (C c f)
(GShow f, GShow g) => GShow (f :*: g)
(GShow f, GShow g) => GShow (f :+: g)
gshow :: (Regular a, GShow (PF a)) => a -> ShowSSource
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 U
LR I
LRBase a => LR (K a)
LR f => LR (C c f)
(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.
Generic folding
type family Alg f r :: *Source
type Algebra a r = Alg (PF a) rSource
class Fold f whereSource
The class fold explains how to convert an algebra Alg into a function from functor to result.
Methods
alg :: Alg f r -> f r -> rSource
show/hide Instances
Fold U
Fold I
Fold (K a)
Fold f => Fold (C c f)
Fold g => Fold (I :*: g)
Fold g => Fold (K a :*: g)
(Fold f, Fold g) => Fold (f :+: g)
fold :: (Regular a, Fold (PF a), Functor (PF a)) => Algebra a r -> a -> rSource
Fold with convenient algebras.
(&) :: a -> b -> (a, b)Source
For constructing algebras it is helpful to use this pairing combinator.
Produced by Haddock version 2.4.2