| 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
- newtype Fix f = Fix {}
- hoistFix :: Functor f => (forall a. f a -> g a) -> Fix f -> Fix g
- hoistFix' :: Functor g => (forall a. f a -> g a) -> Fix f -> Fix g
- foldFix :: Functor f => (f a -> a) -> Fix f -> a
- unfoldFix :: Functor f => (a -> f a) -> a -> Fix f
- newtype Mu f = Mu {- unMu :: forall a. (f a -> a) -> a
 
- hoistMu :: (forall a. f a -> g a) -> Mu f -> Mu g
- foldMu :: (f a -> a) -> Mu f -> a
- unfoldMu :: Functor f => (a -> f a) -> a -> Mu f
- data Nu f = forall a. Nu (a -> f a) a
- hoistNu :: (forall a. f a -> g a) -> Nu f -> Nu g
- foldNu :: Functor f => (f a -> a) -> Nu f -> a
- unfoldNu :: (a -> f a) -> a -> Nu f
- refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- foldFixM :: (Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a
- unfoldFixM :: (Monad m, Traversable t) => (a -> m (t a)) -> a -> m (Fix t)
- refoldM :: (Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b
- cata :: Functor f => (f a -> a) -> Fix f -> a
- ana :: Functor f => (a -> f a) -> a -> Fix f
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- cataM :: (Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a
- anaM :: (Monad m, Traversable t) => (a -> m (t a)) -> a -> m (Fix t)
- hyloM :: (Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b
Fix
A fix-point type.
Instances
| Eq1 f => Eq (Fix f) Source # | |
| (Typeable f, Data (f (Fix f))) => Data (Fix f) Source # | |
| 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) # | |
| Ord1 f => Ord (Fix f) Source # | |
| Read1 f => Read (Fix f) Source # | |
| Show1 f => Show (Fix f) Source # | |
| Generic (Fix f) Source # | |
| NFData1 f => NFData (Fix f) Source # | |
| Hashable1 f => Hashable (Fix f) Source # | |
| type Rep (Fix f) Source # | |
hoistFix :: Functor f => (forall a. f a -> g a) -> Fix f -> Fix g Source #
Change base functor in Fix.
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 (+)) fp6
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))))))))
Mu - least fixed point
Least fixed point. Efficient folding.
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 (+)) mu6
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)))))))))
Nu - greatest fixed point
Greatest fixed point. Efficient unfolding.
Constructors
| forall a. Nu (a -> f a) a | 
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 (+)) nu6
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)))))))))
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
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.