#if __GLASGOW_HASKELL__ >= 707
#endif
#include "free-common.h"
module Control.Monad.Free
( MonadFree(..)
, Free(..)
, retract
, liftF
, iter
, iterA
, iterM
, hoistFree
, foldFree
, toFreeT
, cutoff
, unfold
, unfoldM
, _Pure, _Free
) where
import Control.Applicative
import Control.Arrow ((>>>))
import Control.Monad (liftM, MonadPlus(..), (>=>))
import Control.Monad.Fix
import Control.Monad.Trans.Class
import qualified Control.Monad.Trans.Free as FreeT
import Control.Monad.Free.Class
import Control.Monad.Reader.Class
import Control.Monad.Writer.Class
import Control.Monad.State.Class
import Control.Monad.Error.Class
import Control.Monad.Cont.Class
import Data.Functor.Bind
import Data.Functor.Classes.Compat
import Data.Foldable
import Data.Profunctor
import Data.Traversable
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Data
import Prelude hiding (foldr)
data Free f a = Pure a | Free (f (Free f a))
#if __GLASGOW_HASKELL__ >= 707
deriving (Typeable)
deriving instance (Typeable f, Data (f (Free f a)), Data a) => Data (Free f a)
#endif
#ifdef LIFTED_FUNCTOR_CLASSES
instance Eq1 f => Eq1 (Free f) where
liftEq eq = go
where
go (Pure a) (Pure b) = eq a b
go (Free fa) (Free fb) = liftEq go fa fb
go _ _ = False
#else
instance (Functor f, Eq1 f) => Eq1 (Free f) where
Pure a `eq1` Pure b = a == b
Free fa `eq1` Free fb = fmap Lift1 fa `eq1` fmap Lift1 fb
_ `eq1` _ = False
#endif
#ifdef LIFTED_FUNCTOR_CLASSES
instance (Eq1 f, Eq a) => Eq (Free f a) where
#else
instance (Eq1 f, Functor f, Eq a) => Eq (Free f a) where
#endif
(==) = eq1
#ifdef LIFTED_FUNCTOR_CLASSES
instance Ord1 f => Ord1 (Free f) where
liftCompare cmp = go
where
go (Pure a) (Pure b) = cmp a b
go (Pure _) (Free _) = LT
go (Free _) (Pure _) = GT
go (Free fa) (Free fb) = liftCompare go fa fb
#else
instance (Functor f, Ord1 f) => Ord1 (Free f) where
Pure a `compare1` Pure b = a `compare` b
Pure _ `compare1` Free _ = LT
Free _ `compare1` Pure _ = GT
Free fa `compare1` Free fb = fmap Lift1 fa `compare1` fmap Lift1 fb
#endif
#ifdef LIFTED_FUNCTOR_CLASSES
instance (Ord1 f, Ord a) => Ord (Free f a) where
#else
instance (Ord1 f, Functor f, Ord a) => Ord (Free f a) where
#endif
compare = compare1
#ifdef LIFTED_FUNCTOR_CLASSES
instance Show1 f => Show1 (Free f) where
liftShowsPrec sp sl = go
where
go d (Pure a) = showsUnaryWith sp "Pure" d a
go d (Free fa) = showsUnaryWith (liftShowsPrec go (liftShowList sp sl)) "Free" d fa
#else
instance (Functor f, Show1 f) => Show1 (Free f) where
showsPrec1 d (Pure a) = showParen (d > 10) $
showString "Pure " . showsPrec 11 a
showsPrec1 d (Free m) = showParen (d > 10) $
showString "Free " . showsPrec1 11 (fmap Lift1 m)
#endif
#ifdef LIFTED_FUNCTOR_CLASSES
instance (Show1 f, Show a) => Show (Free f a) where
#else
instance (Show1 f, Functor f, Show a) => Show (Free f a) where
#endif
showsPrec = showsPrec1
#ifdef LIFTED_FUNCTOR_CLASSES
instance Read1 f => Read1 (Free f) where
liftReadsPrec rp rl = go
where
go = readsData $
readsUnaryWith rp "Pure" Pure `mappend`
readsUnaryWith (liftReadsPrec go (liftReadList rp rl)) "Free" Free
#else
instance (Functor f, Read1 f) => Read1 (Free f) where
readsPrec1 d r = readParen (d > 10)
(\r' -> [ (Pure m, t)
| ("Pure", s) <- lex r'
, (m, t) <- readsPrec 11 s]) r
++ readParen (d > 10)
(\r' -> [ (Free (fmap lower1 m), t)
| ("Free", s) <- lex r'
, (m, t) <- readsPrec1 11 s]) r
#endif
#ifdef LIFTED_FUNCTOR_CLASSES
instance (Read1 f, Read a) => Read (Free f a) where
#else
instance (Read1 f, Functor f, Read a) => Read (Free f a) where
#endif
readsPrec = readsPrec1
instance Functor f => Functor (Free f) where
fmap f = go where
go (Pure a) = Pure (f a)
go (Free fa) = Free (go <$> fa)
instance Functor f => Apply (Free f) where
Pure a <.> Pure b = Pure (a b)
Pure a <.> Free fb = Free $ fmap a <$> fb
Free fa <.> b = Free $ (<.> b) <$> fa
instance Functor f => Applicative (Free f) where
pure = Pure
Pure a <*> Pure b = Pure $ a b
Pure a <*> Free mb = Free $ fmap a <$> mb
Free ma <*> b = Free $ (<*> b) <$> ma
instance Functor f => Bind (Free f) where
Pure a >>- f = f a
Free m >>- f = Free ((>>- f) <$> m)
instance Functor f => Monad (Free f) where
return = pure
Pure a >>= f = f a
Free m >>= f = Free ((>>= f) <$> m)
instance Functor f => MonadFix (Free f) where
mfix f = a where a = f (impure a); impure (Pure x) = x; impure (Free _) = error "mfix (Free f): Free"
instance Alternative v => Alternative (Free v) where
empty = Free empty
a <|> b = Free (pure a <|> pure b)
instance (Functor v, MonadPlus v) => MonadPlus (Free v) where
mzero = Free mzero
a `mplus` b = Free (return a `mplus` return b)
instance MonadTrans Free where
lift = Free . liftM Pure
instance Foldable f => Foldable (Free f) where
foldMap f = go where
go (Pure a) = f a
go (Free fa) = foldMap go fa
foldr f = go where
go r free =
case free of
Pure a -> f a r
Free fa -> foldr (flip go) r fa
#if MIN_VERSION_base(4,6,0)
foldl' f = go where
go r free =
case free of
Pure a -> f r a
Free fa -> foldl' go r fa
#endif
instance Foldable1 f => Foldable1 (Free f) where
foldMap1 f = go where
go (Pure a) = f a
go (Free fa) = foldMap1 go fa
instance Traversable f => Traversable (Free f) where
traverse f = go where
go (Pure a) = Pure <$> f a
go (Free fa) = Free <$> traverse go fa
instance Traversable1 f => Traversable1 (Free f) where
traverse1 f = go where
go (Pure a) = Pure <$> f a
go (Free fa) = Free <$> traverse1 go fa
instance (Functor m, MonadWriter e m) => MonadWriter e (Free m) where
tell = lift . tell
listen = lift . listen . retract
pass = lift . pass . retract
instance (Functor m, MonadReader e m) => MonadReader e (Free m) where
ask = lift ask
local f = lift . local f . retract
instance (Functor m, MonadState s m) => MonadState s (Free m) where
get = lift get
put s = lift (put s)
instance (Functor m, MonadError e m) => MonadError e (Free m) where
throwError = lift . throwError
catchError as f = lift (catchError (retract as) (retract . f))
instance (Functor m, MonadCont m) => MonadCont (Free m) where
callCC f = lift (callCC (retract . f . liftM lift))
instance Functor f => MonadFree f (Free f) where
wrap = Free
retract :: Monad f => Free f a -> f a
retract (Pure a) = return a
retract (Free as) = as >>= retract
iter :: Functor f => (f a -> a) -> Free f a -> a
iter _ (Pure a) = a
iter phi (Free m) = phi (iter phi <$> m)
iterA :: (Applicative p, Functor f) => (f (p a) -> p a) -> Free f a -> p a
iterA _ (Pure x) = pure x
iterA phi (Free f) = phi (iterA phi <$> f)
iterM :: (Monad m, Functor f) => (f (m a) -> m a) -> Free f a -> m a
iterM _ (Pure x) = return x
iterM phi (Free f) = phi (iterM phi <$> f)
hoistFree :: Functor g => (forall a. f a -> g a) -> Free f b -> Free g b
hoistFree _ (Pure a) = Pure a
hoistFree f (Free as) = Free (hoistFree f <$> f as)
foldFree :: Monad m => (forall x . f x -> m x) -> Free f a -> m a
foldFree _ (Pure a) = return a
foldFree f (Free as) = f as >>= foldFree f
toFreeT :: (Functor f, Monad m) => Free f a -> FreeT.FreeT f m a
toFreeT (Pure a) = FreeT.FreeT (return (FreeT.Pure a))
toFreeT (Free f) = FreeT.FreeT (return (FreeT.Free (fmap toFreeT f)))
cutoff :: (Functor f) => Integer -> Free f a -> Free f (Maybe a)
cutoff n _ | n <= 0 = return Nothing
cutoff n (Free f) = Free $ fmap (cutoff (n 1)) f
cutoff _ m = Just <$> m
unfold :: Functor f => (b -> Either a (f b)) -> b -> Free f a
unfold f = f >>> either Pure (Free . fmap (unfold f))
unfoldM :: (Traversable f, Applicative m, Monad m) => (b -> m (Either a (f b))) -> b -> m (Free f a)
unfoldM f = f >=> either (pure . pure) (fmap Free . traverse (unfoldM f))
_Pure :: forall f m a p. (Choice p, Applicative m)
=> p a (m a) -> p (Free f a) (m (Free f a))
_Pure = dimap impure (either pure (fmap Pure)) . right'
where
impure (Pure x) = Right x
impure x = Left x
_Free :: forall f m a p. (Choice p, Applicative m)
=> p (f (Free f a)) (m (f (Free f a))) -> p (Free f a) (m (Free f a))
_Free = dimap unfree (either pure (fmap Free)) . right'
where
unfree (Free x) = Right x
unfree x = Left x
#if __GLASGOW_HASKELL__ < 707
instance Typeable1 f => Typeable1 (Free f) where
typeOf1 t = mkTyConApp freeTyCon [typeOf1 (f t)] where
f :: Free f a -> f a
f = undefined
freeTyCon :: TyCon
#if __GLASGOW_HASKELL__ < 704
freeTyCon = mkTyCon "Control.Monad.Free.Free"
#else
freeTyCon = mkTyCon3 "free" "Control.Monad.Free" "Free"
#endif
instance
( Typeable1 f, Typeable a
, Data a, Data (f (Free f a))
) => Data (Free f a) where
gfoldl f z (Pure a) = z Pure `f` a
gfoldl f z (Free as) = z Free `f` as
toConstr Pure{} = pureConstr
toConstr Free{} = freeConstr
gunfold k z c = case constrIndex c of
1 -> k (z Pure)
2 -> k (z Free)
_ -> error "gunfold"
dataTypeOf _ = freeDataType
dataCast1 f = gcast1 f
pureConstr, freeConstr :: Constr
pureConstr = mkConstr freeDataType "Pure" [] Prefix
freeConstr = mkConstr freeDataType "Free" [] Prefix
freeDataType :: DataType
freeDataType = mkDataType "Control.Monad.Free.FreeF" [pureConstr, freeConstr]
#endif