{-# OPTIONS -fallow-undecidable-instances #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.List -- Copyright : (c) Andy Gill 2001, -- (c) Oregon Graduate Institute of Science and Technology 2001, -- (c) Mauro Jaskelioff 2008, -- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : mjj@cs.nott.ac.uk -- Stability : experimental -- Portability : non-portable (multi-parameter type classes) -- -- The List monad. -- ----------------------------------------------------------------------------- module Control.Monad.List ( ListT(..), mapListT, module Control.Monad, module Control.Monad.Trans, ) where import Control.Monad import Control.Monad.Trans -- --------------------------------------------------------------------------- -- Our parameterizable list monad, with an inner monad newtype ListT m a = ListT { runListT :: m [a] } mapListT :: (m [a] -> n [b]) -> ListT m a -> ListT n b mapListT f m = ListT $ f (runListT m) instance (Monad m) => Functor (ListT m) where fmap f m = ListT $ do a <- runListT m return (map f a) instance (Monad m) => Monad (ListT m) where return a = ListT $ return [a] m >>= k = ListT $ do a <- runListT m b <- mapM (runListT . k) a return (concat b) fail _ = ListT $ return [] instance (Monad m) => MonadPlus (ListT m) where mzero = ListT $ return [] m `mplus` n = ListT $ do a <- runListT m b <- runListT n return (a ++ b) -- --------------------------------------------------------------------------- -- Instances for other mtl transformers instance (Monad m, MonadTrans t, Monad (t (ListT m))) => MonadPlus (t (ListT m)) where mzero = lift $ ListT $ return [] mplus m n = join $ lift $ ListT $ return [m,n] instance MonadTrans ListT where lift m = ListT $ do a <- m return [a] tmap f _ = ListT . f . runListT instance (MonadIO m) => MonadIO (ListT m) where liftIO = lift . liftIO