module Data.Fix (
Fix(..)
, cata
, ana
, hylo
, (~>)
, cataM
, anaM
, hyloM
)
where
import GHC.Generics
import Control.Applicative
import Data.Data
import Data.Function (on)
import Data.Traversable
newtype Fix f = Fix { unFix :: f (Fix f) } deriving (Generic, Typeable)
deriving instance (Typeable f, Data (f (Fix f))) => Data (Fix f)
instance Show (f (Fix f)) => Show (Fix f) where
showsPrec n x = showParen (n > 10) $ \s ->
"Fix " ++ showsPrec 11 (unFix x) s
instance Read (f (Fix f)) => Read (Fix f) where
readsPrec d = readParen (d > 10) $ \r ->
[(Fix m, t) | ("Fix", s) <- lex r, (m, t) <- readsPrec 11 s]
instance Eq (f (Fix f)) => Eq (Fix f) where
(==) = (==) `on` unFix
instance Ord (f (Fix f)) => Ord (Fix f) where
compare = compare `on` unFix
cata :: Functor f => (f a -> a) -> (Fix f -> a)
cata f = f . fmap (cata f) . unFix
ana :: Functor f => (a -> f a) -> (a -> Fix f)
ana f = Fix . fmap (ana f) . f
hylo :: Functor f => (f b -> b) -> (a -> f a) -> (a -> b)
hylo phi psi = cata phi . ana psi
(~>) :: Functor f => (a -> f a) -> (f b -> b) -> (a -> b)
psi ~> phi = phi . fmap (hylo phi psi) . psi
cataM :: (Applicative m, Monad m, Traversable t)
=> (t a -> m a) -> Fix t -> m a
cataM f = (f =<<) . traverse (cataM f) . unFix
anaM :: (Applicative m, Monad m, Traversable t)
=> (a -> m (t a)) -> (a -> m (Fix t))
anaM f = fmap Fix . (traverse (anaM f) =<<) . f
hyloM :: (Applicative m, Monad m, Traversable t)
=> (t b -> m b) -> (a -> m (t a)) -> (a -> m b)
hyloM phi psi = (cataM phi =<<) . anaM psi