From ebbb68be22d861cd38915edd259e7e0b3b894e10 Mon Sep 17 00:00:00 2001 From: Artyom Date: Tue, 5 Apr 2016 12:38:19 +0300 Subject: [PATCH] Generalise hoistCofree --- src/Control/Comonad/Cofree.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Control/Comonad/Cofree.hs b/src/Control/Comonad/Cofree.hs index ea33bdd..56d3c47 100644 --- a/src/Control/Comonad/Cofree.hs +++ b/src/Control/Comonad/Cofree.hs @@ -1,5 +1,4 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE Rank2Types #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} @@ -125,7 +124,7 @@ unfold f c = case f c of unfoldM :: (Traversable f, Monad m) => (b -> m (a, f b)) -> b -> m (Cofree f a) unfoldM f = f >=> \ (x, t) -> (x :<) `liftM` Data.Traversable.mapM (unfoldM f) t -hoistCofree :: Functor f => (forall x . f x -> g x) -> Cofree f a -> Cofree g a +hoistCofree :: Functor f => (f (Cofree g a) -> g (Cofree g a)) -> Cofree f a -> Cofree g a hoistCofree f (x :< y) = x :< f (hoistCofree f <$> y) instance Functor f => ComonadCofree f (Cofree f) where @@ -302,7 +301,7 @@ cofreeDataType = mkDataType "Control.Comonad.Cofree.Cofree" [cofreeConstr] #endif instance ComonadHoist Cofree where - cohoist = hoistCofree + cohoist f = hoistCofree f instance ComonadEnv e w => ComonadEnv e (Cofree w) where ask = ask . lower