Copyright | Copyright (c) 2007--2024 wren gayle romano |
---|---|
License | BSD |
Maintainer | wren@cpan.org |
Stability | deprecated since unification-fd-0.12.0 |
Portability | semi-portable (Rank2Types) |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Data.Functor.Fixedpoint
Description
This module provides a backwards compatibility shim for users
of older versions of unification-fd
, before we switched over
to using data-fix
. New users should prefer calling data-fix
functions directly, whenever possible. If you use any of the
functions that aren't deprecated (hoistFixM
, ymap
, ymapM
,
ycata
, ycataM
, build
), please let the maintainer know,
so she can focus on getting those incorporated into data-fix
.
Returning users should beware that this module used to provide
rewrite rules for fusing redundant traversals of data structures
(which data-fix
does not). If you notice version >=0.12.0
introducing any performance loss compared to earlier versions,
please let the maintainer know, so she can focus on getting those
incorporated into data-fix
.
This abstract nonsense is helpful in conjunction with other category theoretic tricks like Swierstra's functor coproducts (not provided by this package). For more on the utility of two-level recursive types, see:
- Tim Sheard (2001) Generic Unification via Two-Level Types and Parameterized Modules, Functional Pearl, ICFP.
- Tim Sheard & Emir Pasalic (2004) Two-Level Types and Parameterized Modules. JFP 14(5): 547--587. This is an expanded version of Sheard (2001) with new examples.
- Wouter Swierstra (2008) Data types a la carte, Functional Pearl. JFP 18: 423--436.
Synopsis
- newtype Fix (f :: Type -> Type) = Fix {}
- hmap :: (Functor f, Functor g) => (forall a. f a -> g a) -> Fix f -> Fix g
- hmapM :: (Functor f, Traversable g, Monad m) => (forall a. f a -> m (g a)) -> Fix f -> m (Fix g)
- hoistFixM' :: (Functor f, Traversable g, Monad m) => (forall a. f a -> m (g a)) -> Fix f -> m (Fix g)
- ymap :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f
- ymapM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f)
- build :: Functor f => (forall r. (f r -> r) -> r) -> Fix f
- cata :: Functor f => (f a -> a) -> Fix f -> a
- cataM :: (Traversable f, Monad m) => (f a -> m a) -> Fix f -> m a
- ycata :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f
- ycataM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f)
- ana :: Functor f => (a -> f a) -> a -> Fix f
- anaM :: (Traversable f, Monad m) => (a -> m (f a)) -> a -> m (Fix f)
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- hyloM :: (Traversable f, Monad m) => (f b -> m b) -> (a -> m (f a)) -> a -> m b
Fixed point operator for functors
newtype Fix (f :: Type -> Type) #
A fix-point type.
Instances
(Typeable f, Data (f (Fix f))) => Data (Fix f) | |
Defined in Data.Fix Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fix f -> c (Fix f) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fix f) # dataTypeOf :: Fix f -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fix f)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fix f)) # gmapT :: (forall b. Data b => b -> b) -> Fix f -> Fix f # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r # gmapQ :: (forall d. Data d => d -> u) -> Fix f -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fix f -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) # | |
Generic (Fix f) | |
Read1 f => Read (Fix f) | |
Show1 f => Show (Fix f) | |
NFData1 f => NFData (Fix f) | |
Eq1 f => Eq (Fix f) | |
Ord1 f => Ord (Fix f) | |
Hashable1 f => Hashable (Fix f) | |
type Rep (Fix f) | |
Maps
hmap :: (Functor f, Functor g) => (forall a. f a -> g a) -> Fix f -> Fix g Source #
Deprecated: Use Data.Fix.hoistFix'
A higher-order map taking a natural transformation (f -> g)
and lifting it to operate on Fix
.
NOTE: The implementation of hmap
prior to version 0.12 was
based on ana
, and therefore most closely matches the behavior
of hoistFix'
. However, this definition is extensionally
equivalent to an implementation using cata
(and therefore most
closely matches the behavior of hoistFix
) instead.
hmapM :: (Functor f, Traversable g, Monad m) => (forall a. f a -> m (g a)) -> Fix f -> m (Fix g) Source #
Deprecated: Use hoistFixM'
A monadic variant of hmap
.
hoistFixM' :: (Functor f, Traversable g, Monad m) => (forall a. f a -> m (g a)) -> Fix f -> m (Fix g) Source #
A monadic variant of hoistFix'
.
NOTE: The implementation of hmapM
prior to version 0.12 was
based on anaM
, and therefore most closely matches the behavior
of unfoldFixM
. However, there is another function
of the same type which is instead implemented via cataM
,
which has different semantics for many monads.
ymap :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f Source #
A version of fmap
for endomorphisms on the fixed point. That
is, this maps the function over the first layer of recursive
structure.
ymapM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f) Source #
A monadic variant of ymap
.
Builders
build :: Functor f => (forall r. (f r -> r) -> r) -> Fix f Source #
Take a Church encoding of a fixed point into the data representation of the fixed point.
Catamorphisms
cata :: Functor f => (f a -> a) -> Fix f -> a Source #
Deprecated: Use Data.Fix.foldFix
A pure catamorphism over the least fixed point of a functor.
This function applies the f
-algebra from the bottom up over
Fix f
to create some residual value.
cataM :: (Traversable f, Monad m) => (f a -> m a) -> Fix f -> m a Source #
Deprecated: Use Data.Fix.foldFixM
A catamorphism for monadic f
-algebras. Alas, this isn't wholly
generic to Functor
since it requires distribution of f
over
m
(provided by sequence
or mapM
in Traversable
).
N.B., this orders the side effects from the bottom up.
ycata :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f Source #
A variant of cata
which restricts the return type to being
a new fixpoint. Though more restrictive, it can be helpful when
you already have an algebra which expects the outermost Fix
.
If you don't like either fmap
or cata
, then maybe this is
what you were thinking?
ycataM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f) Source #
Monadic variant of ycata
.
Anamorphisms
ana :: Functor f => (a -> f a) -> a -> Fix f Source #
Deprecated: Use Data.Fix.unfoldFix
A pure anamorphism generating the greatest fixed point of a
functor. This function applies an f
-coalgebra from the top
down to expand a seed into a Fix f
.
anaM :: (Traversable f, Monad m) => (a -> m (f a)) -> a -> m (Fix f) Source #
Deprecated: Use Data.Fix.unfoldFixM
An anamorphism for monadic f
-coalgebras. Alas, this isn't
wholly generic to Functor
since it requires distribution of
f
over m
(provided by sequence
or mapM
in Traversable
).
N.B., this orders the side effects from the top down.
Hylomorphisms
hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #
Deprecated: Use Data.Fix.refold
hylo phi psi == cata phi . ana psi
hyloM :: (Traversable f, Monad m) => (f b -> m b) -> (a -> m (f a)) -> a -> m b Source #
Deprecated: Use Data.Fix.refoldM
hyloM phiM psiM == cataM phiM <=< anaM psiM