#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 710
#endif
module Control.Monad.Trans.List
(
ListT(..),
mapListT,
liftCallCC,
liftCatch,
) where
import Control.Monad.IO.Class
import Control.Monad.Signatures
import Control.Monad.Trans.Class
import Data.Functor.Classes
#if MIN_VERSION_base(4,12,0)
import Data.Functor.Contravariant
#endif
import Control.Applicative
import Control.Monad
#if MIN_VERSION_base(4,9,0)
import qualified Control.Monad.Fail as Fail
#endif
import Control.Monad.Fix
#if MIN_VERSION_base(4,4,0)
import Control.Monad.Zip (MonadZip(mzipWith))
#endif
import Data.Foldable (Foldable(foldMap))
import Data.Traversable (Traversable(traverse))
newtype ListT m a = ListT { runListT :: m [a] }
instance (Eq1 m) => Eq1 (ListT m) where
liftEq eq (ListT x) (ListT y) = liftEq (liftEq eq) x y
instance (Ord1 m) => Ord1 (ListT m) where
liftCompare comp (ListT x) (ListT y) = liftCompare (liftCompare comp) x y
instance (Read1 m) => Read1 (ListT m) where
liftReadsPrec rp rl = readsData $
readsUnaryWith (liftReadsPrec rp' rl') "ListT" ListT
where
rp' = liftReadsPrec rp rl
rl' = liftReadList rp rl
instance (Show1 m) => Show1 (ListT m) where
liftShowsPrec sp sl d (ListT m) =
showsUnaryWith (liftShowsPrec sp' sl') "ListT" d m
where
sp' = liftShowsPrec sp sl
sl' = liftShowList sp sl
instance (Eq1 m, Eq a) => Eq (ListT m a) where (==) = eq1
instance (Ord1 m, Ord a) => Ord (ListT m a) where compare = compare1
instance (Read1 m, Read a) => Read (ListT m a) where readsPrec = readsPrec1
instance (Show1 m, Show a) => Show (ListT m a) where showsPrec = showsPrec1
mapListT :: (m [a] -> n [b]) -> ListT m a -> ListT n b
mapListT f m = ListT $ f (runListT m)
instance (Functor m) => Functor (ListT m) where
fmap f = mapListT $ fmap $ map f
instance (Foldable f) => Foldable (ListT f) where
foldMap f (ListT a) = foldMap (foldMap f) a
instance (Traversable f) => Traversable (ListT f) where
traverse f (ListT a) = ListT <$> traverse (traverse f) a
instance (Applicative m) => Applicative (ListT m) where
pure a = ListT $ pure [a]
f <*> v = ListT $ (<*>) <$> runListT f <*> runListT v
instance (Applicative m) => Alternative (ListT m) where
empty = ListT $ pure []
m <|> n = ListT $ (++) <$> runListT m <*> runListT n
instance (Monad m) => Monad (ListT m) where
#if !(MIN_VERSION_base(4,8,0))
return a = ListT $ return [a]
#endif
m >>= k = ListT $ do
a <- runListT m
b <- mapM (runListT . k) a
return (concat b)
#if !(MIN_VERSION_base(4,13,0))
fail _ = ListT $ return []
#endif
#if MIN_VERSION_base(4,9,0)
instance (Monad m) => Fail.MonadFail (ListT m) where
fail _ = ListT $ return []
#endif
instance (Monad m) => MonadPlus (ListT m) where
mzero = ListT $ return []
m `mplus` n = ListT $ do
a <- runListT m
b <- runListT n
return (a ++ b)
instance (MonadFix m) => MonadFix (ListT m) where
mfix f = ListT $ mfix (runListT . f . head) >>= \ xs -> case xs of
[] -> return []
x:_ -> liftM (x:) (runListT (mfix (mapListT (liftM tail) . f)))
instance MonadTrans ListT where
lift m = ListT $ do
a <- m
return [a]
instance (MonadIO m) => MonadIO (ListT m) where
liftIO = lift . liftIO
#if MIN_VERSION_base(4,4,0)
instance (MonadZip m) => MonadZip (ListT m) where
mzipWith f (ListT a) (ListT b) = ListT $ mzipWith (zipWith f) a b
#endif
#if MIN_VERSION_base(4,12,0)
instance Contravariant m => Contravariant (ListT m) where
contramap f = ListT . contramap (fmap f) . runListT
#endif
liftCallCC :: CallCC m [a] [b] -> CallCC (ListT m) a b
liftCallCC callCC f = ListT $
callCC $ \ c ->
runListT (f (\ a -> ListT $ c [a]))
liftCatch :: Catch e m [a] -> Catch e (ListT m) a
liftCatch catchE m h = ListT $ runListT m
`catchE` \ e -> runListT (h e)