data-fix-0.3.2: Fixpoint data types
Safe Haskell Trustworthy
Language Haskell2010

Data.Fix

Description

Fixed points of a functor.

Type f should be a Functor if you want to use simple recursion schemes or Traversable if you want to use monadic recursion schemes. This style allows you to express recursive functions in non-recursive manner. You can imagine that a non-recursive function holds values of the previous iteration.

An example:

First we define a base functor. The arguments b are recursion points.

>>> data ListF a b = Nil | Cons a b deriving (Show, Functor)

The list is then a fixed point of ListF

>>> type List a = Fix (ListF a)

We can write length function. Note that the function we give to foldFix is not recursive. Instead the results of recursive calls are in b positions, and we need to deal only with one layer of the structure.

>>> :{
let length :: List a -> Int
    length = foldFix $ \x -> case x of
        Nil      -> 0
        Cons _ n -> n + 1
:}

If you already have recursive type, like '[Int]', you can first convert it to `Fix (ListF a)` and then foldFix . Alternatively you can use recursion-schemes combinators which work directly on recursive types.

Synopsis

Fix

newtype Fix f Source #

A fix-point type.

Constructors

Fix

Fields

Instances

Instances details
Eq1 f => Eq ( Fix f) Source #
Instance details

Defined in Data.Fix

( Typeable f, Data (f ( Fix f))) => Data ( Fix f) Source #
Instance details

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) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Fix f) Source #

toConstr :: Fix f -> Constr Source #

dataTypeOf :: Fix f -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Fix f)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Fix f)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Fix f -> Fix f Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Fix f -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Fix f -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Fix f -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Fix f -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Fix f -> m ( Fix f) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Fix f -> m ( Fix f) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Fix f -> m ( Fix f) Source #

Ord1 f => Ord ( Fix f) Source #
Instance details

Defined in Data.Fix

Read1 f => Read ( Fix f) Source #
Instance details

Defined in Data.Fix

Show1 f => Show ( Fix f) Source #
Instance details

Defined in Data.Fix

Generic ( Fix f) Source #
Instance details

Defined in Data.Fix

Associated Types

type Rep ( Fix f) :: Type -> Type Source #

NFData1 f => NFData ( Fix f) Source #
Instance details

Defined in Data.Fix

Methods

rnf :: Fix f -> () Source #

Hashable1 f => Hashable ( Fix f) Source #
Instance details

Defined in Data.Fix

type Rep ( Fix f) Source #
Instance details

Defined in Data.Fix

type Rep ( Fix f) = D1 (' MetaData "Fix" "Data.Fix" "data-fix-0.3.2-LpD4EKXxVVUJR8w9NGWPdd" ' True ) ( C1 (' MetaCons "Fix" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "unFix") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 (f ( Fix f)))))

hoistFix :: Functor f => ( forall a. f a -> g a) -> Fix f -> Fix g Source #

Change base functor in Fix .

hoistFix' :: Functor g => ( forall a. f a -> g a) -> Fix f -> Fix g Source #

Like hoistFix but fmap ping over g .

foldFix :: Functor f => (f a -> a) -> Fix f -> a Source #

Fold Fix .

>>> let fp = unfoldFix (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
>>> foldFix (elimListF 0 (+)) fp
6

unfoldFix :: Functor f => (a -> f a) -> a -> Fix f Source #

Unfold Fix .

>>> unfoldFix (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix (Cons 3 (Fix Nil))))))))

wrapFix :: f ( Fix f) -> Fix f Source #

Wrap Fix .

>>> let x = unfoldFix (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> wrapFix (Cons 10 x)
Fix (Cons 10 (Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix Nil))))))))

Since: 0.3.2

unwrapFix :: Fix f -> f ( Fix f) Source #

Unwrap Fix .

>>> let x = unfoldFix (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> unwrapFix x
Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix Nil)))))

Since: 0.3.2

Mu - least fixed point

hoistMu :: ( forall a. f a -> g a) -> Mu f -> Mu g Source #

Change base functor in Mu .

foldMu :: (f a -> a) -> Mu f -> a Source #

Fold Mu .

>>> let mu = unfoldMu (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
>>> foldMu (elimListF 0 (+)) mu
6

unfoldMu :: Functor f => (a -> f a) -> a -> Mu f Source #

Unfold Mu .

>>> unfoldMu (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
unfoldMu unFix (Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix (Cons 3 (Fix Nil)))))))))

wrapMu :: Functor f => f ( Mu f) -> Mu f Source #

Wrap Mu .

>>> let x = unfoldMu (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> wrapMu (Cons 10 x)
unfoldMu unFix (Fix (Cons 10 (Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix Nil)))))))))

Since: 0.3.2

unwrapMu :: Functor f => Mu f -> f ( Mu f) Source #

Unwrap Mu .

>>> let x = unfoldMu (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> unwrapMu x
Cons 0 (unfoldMu unFix (Fix (Cons 1 (Fix (Cons 2 (Fix Nil))))))

Since: 0.3.2

Nu - greatest fixed point

hoistNu :: ( forall a. f a -> g a) -> Nu f -> Nu g Source #

Change base functor in Nu .

foldNu :: Functor f => (f a -> a) -> Nu f -> a Source #

Fold Nu .

>>> let nu = unfoldNu (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
>>> foldNu (elimListF 0 (+)) nu
6

unfoldNu :: (a -> f a) -> a -> Nu f Source #

Unfold Nu .

>>> unfoldNu (\i -> if i < 4 then Cons i (i + 1) else Nil) (0 :: Int)
unfoldNu unFix (Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix (Cons 3 (Fix Nil)))))))))

wrapNu :: Functor f => f ( Nu f) -> Nu f Source #

Wrap Nu .

>>> let x = unfoldNu (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> wrapNu (Cons 10 x)
unfoldNu unFix (Fix (Cons 10 (Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix Nil)))))))))

Since: 0.3.2

unwrapNu :: Functor f => Nu f -> f ( Nu f) Source #

Unwrap Nu .

>>> let x = unfoldNu (\i -> if i < 3 then Cons i (i + 1) else Nil) (0 :: Int)
>>> unwrapNu x
Cons 0 (unfoldNu unFix (Fix (Cons 1 (Fix (Cons 2 (Fix Nil))))))

Since: 0.3.2

Refolding

refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

Refold one recursive type into another, one layer at the time.

Monadic variants

foldFixM :: ( Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a Source #

Monadic foldFix .

unfoldFixM :: ( Monad m, Traversable t) => (a -> m (t a)) -> a -> m ( Fix t) Source #

Monadic anamorphism.

refoldM :: ( Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b Source #

Monadic hylomorphism.

Deprecated aliases

cata :: Functor f => (f a -> a) -> Fix f -> a Source #

Deprecated: Use foldFix

Catamorphism or generic function fold.

ana :: Functor f => (a -> f a) -> a -> Fix f Source #

Deprecated: Use unfoldFix

Anamorphism or generic function unfold.

hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

Deprecated: Use refold

Hylomorphism is anamorphism followed by catamorphism.

cataM :: ( Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a Source #

Deprecated: Use foldFixM

Monadic catamorphism.

anaM :: ( Monad m, Traversable t) => (a -> m (t a)) -> a -> m ( Fix t) Source #

Deprecated: Use unfoldFixM

Monadic anamorphism.

hyloM :: ( Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b Source #

Deprecated: Use refoldM

Monadic hylomorphism.