{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UndecidableInstances #-}
#define HAS_POLY_TYPEABLE MIN_VERSION_base(4,7,0)
#if HAS_POLY_TYPEABLE
{-# LANGUAGE StandaloneDeriving #-}
#endif
module Data.Fix (
Fix (..),
hoistFix,
hoistFix',
foldFix,
unfoldFix,
Mu (..),
hoistMu,
foldMu,
unfoldMu,
Nu (..),
hoistNu,
foldNu,
unfoldNu,
refold,
foldFixM,
unfoldFixM,
refoldM,
cata, ana, hylo,
cataM, anaM, hyloM,
) where
import Data.Traversable (Traversable (..))
import Prelude (Eq (..), Functor (..), Monad (..), Ord (..), Read (..), Show (..), showParen, showString, ($), (.), (=<<))
#ifdef __GLASGOW_HASKELL__
#if! HAS_POLY_TYPEABLE
import Prelude (const, error, undefined)
#endif
#endif
import Control.Monad (liftM)
import Data.Function (on)
import Data.Functor.Classes (Eq1, Ord1, Read1, Show1, compare1, eq1, readsPrec1, showsPrec1)
import Data.Hashable (Hashable (..))
import Data.Hashable.Lifted (Hashable1, hashWithSalt1)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Read (Lexeme (Ident), Read (..), lexP, parens, prec, readS_to_Prec, step)
#if MIN_VERSION_deepseq(1,4,3)
import Control.DeepSeq (NFData (..), NFData1, rnf1)
#endif
#if HAS_POLY_TYPEABLE
import Data.Data (Data)
#else
import Data.Data
#endif
newtype Fix f = Fix { unFix :: f (Fix f) }
deriving (Generic)
hoistFix :: Functor f => (forall a. f a -> g a) -> Fix f -> Fix g
hoistFix nt = go where go (Fix f) = Fix (nt (fmap go f))
hoistFix' :: Functor g => (forall a. f a -> g a) -> Fix f -> Fix g
hoistFix' nt = go where go (Fix f) = Fix (fmap go (nt f))
foldFix :: Functor f => (f a -> a) -> Fix f -> a
foldFix f = go where go = f . fmap go . unFix
unfoldFix :: Functor f => (a -> f a) -> a -> Fix f
unfoldFix f = go where go = Fix . fmap go . f
instance Eq1 f => Eq (Fix f) where
Fix a == Fix b = eq1 a b
instance Ord1 f => Ord (Fix f) where
compare (Fix a) (Fix b) = compare1 a b
instance Show1 f => Show (Fix f) where
showsPrec d (Fix a) =
showParen (d >= 11)
$ showString "Fix "
. showsPrec1 11 a
#ifdef __GLASGOW_HASKELL__
instance Read1 f => Read (Fix f) where
readPrec = parens $ prec 10 $ do
Ident "Fix" <- lexP
fmap Fix (step (readS_to_Prec readsPrec1))
#endif
instance Hashable1 f => Hashable (Fix f) where
hashWithSalt salt = hashWithSalt1 salt . unFix
#if MIN_VERSION_deepseq(1,4,3)
instance NFData1 f => NFData (Fix f) where
rnf = rnf1 . unFix
#endif
#ifdef __GLASGOW_HASKELL__
#if HAS_POLY_TYPEABLE
deriving instance Typeable Fix
deriving instance (Typeable f, Data (f (Fix f))) => Data (Fix f)
#else
instance Typeable1 f => Typeable (Fix f) where
typeOf t = mkTyConApp fixTyCon [typeOf1 (undefined `asArgsTypeOf` t)]
where asArgsTypeOf :: f a -> Fix f -> f a
asArgsTypeOf = const
fixTyCon :: TyCon
#if MIN_VERSION_base(4,4,0)
fixTyCon = mkTyCon3 "recursion-schemes" "Data.Functor.Foldable" "Fix"
#else
fixTyCon = mkTyCon "Data.Functor.Foldable.Fix"
#endif
{-# NOINLINE fixTyCon #-}
instance (Typeable1 f, Data (f (Fix f))) => Data (Fix f) where
gfoldl f z (Fix a) = z Fix `f` a
toConstr _ = fixConstr
gunfold k z c = case constrIndex c of
1 -> k (z (Fix))
_ -> error "gunfold"
dataTypeOf _ = fixDataType
fixConstr :: Constr
fixConstr = mkConstr fixDataType "Fix" [] Prefix
fixDataType :: DataType
fixDataType = mkDataType "Data.Functor.Foldable.Fix" [fixConstr]
#endif
#endif
newtype Mu f = Mu { unMu :: forall a. (f a -> a) -> a }
instance (Functor f, Eq1 f) => Eq (Mu f) where
(==) = (==) `on` foldMu Fix
instance (Functor f, Ord1 f) => Ord (Mu f) where
compare = compare `on` foldMu Fix
instance (Functor f, Show1 f) => Show (Mu f) where
showsPrec d f = showParen (d > 10) $
showString "unfoldMu unFix " . showsPrec 11 (foldMu Fix f)
#ifdef __GLASGOW_HASKELL__
instance (Functor f, Read1 f) => Read (Mu f) where
readPrec = parens $ prec 10 $ do
Ident "unfoldMu" <- lexP
Ident "unFix" <- lexP
fmap (unfoldMu unFix) (step readPrec)
#endif
hoistMu :: (forall a. f a -> g a) -> Mu f -> Mu g
hoistMu n (Mu mk) = Mu $ \roll -> mk (roll . n)
foldMu :: (f a -> a) -> Mu f -> a
foldMu f (Mu mk) = mk f
unfoldMu :: Functor f => (a -> f a) -> a -> Mu f
unfoldMu f x = Mu $ \mk -> refold mk f x
data Nu f = forall a. Nu (a -> f a) a
instance (Functor f, Eq1 f) => Eq (Nu f) where
(==) = (==) `on` foldNu Fix
instance (Functor f, Ord1 f) => Ord (Nu f) where
compare = compare `on` foldNu Fix
instance (Functor f, Show1 f) => Show (Nu f) where
showsPrec d f = showParen (d > 10) $
showString "unfoldNu unFix " . showsPrec 11 (foldNu Fix f)
#ifdef __GLASGOW_HASKELL__
instance (Functor f, Read1 f) => Read (Nu f) where
readPrec = parens $ prec 10 $ do
Ident "unfoldNu" <- lexP
Ident "unFix" <- lexP
fmap (unfoldNu unFix) (step readPrec)
#endif
hoistNu :: (forall a. f a -> g a) -> Nu f -> Nu g
hoistNu n (Nu next seed) = Nu (n . next) seed
foldNu :: Functor f => (f a -> a) -> Nu f -> a
foldNu f (Nu next seed) = refold f next seed
unfoldNu :: (a -> f a) -> a -> Nu f
unfoldNu = Nu
refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
refold f g = h where h = f . fmap h . g
foldFixM:: (Monad m, Traversable t)
=> (t a -> m a) -> Fix t -> m a
foldFixM f = go where go = (f =<<) . mapM go . unFix
unfoldFixM :: (Monad m, Traversable t)
=> (a -> m (t a)) -> (a -> m (Fix t))
unfoldFixM f = go where go = liftM Fix . (mapM go =<<) . f
refoldM :: (Monad m, Traversable t)
=> (t b -> m b) -> (a -> m (t a)) -> (a -> m b)
refoldM phi psi = go where go = (phi =<<) . (mapM go =<<) . psi
cata :: Functor f => (f a -> a) -> (Fix f -> a)
cata = foldFix
{-# DEPRECATED cata "Use foldFix" #-}
ana :: Functor f => (a -> f a) -> (a -> Fix f)
ana = unfoldFix
{-# DEPRECATED ana "Use unfoldFix" #-}
hylo :: Functor f => (f b -> b) -> (a -> f a) -> (a -> b)
hylo = refold
{-# DEPRECATED hylo "Use refold" #-}
cataM :: (Monad m, Traversable t)
=> (t a -> m a) -> Fix t -> m a
cataM = foldFixM
{-# DEPRECATED cataM "Use foldFixM" #-}
anaM :: (Monad m, Traversable t)
=> (a -> m (t a)) -> (a -> m (Fix t))
anaM = unfoldFixM
{-# DEPRECATED anaM "Use unfoldFixM" #-}
hyloM :: (Monad m, Traversable t)
=> (t b -> m b) -> (a -> m (t a)) -> (a -> m b)
hyloM = refoldM
{-# DEPRECATED hyloM "Use refoldM" #-}