[Haskell-beginners] partitionM

Daniel Fischer daniel.is.fischer at web.de
Thu Dec 3 18:53:17 EST 2009


Am Donnerstag 03 Dezember 2009 22:06:19 schrieb Daniel Fischer:
> Am Donnerstag 03 Dezember 2009 21:33:53 schrieb Tom Tobin:
> > While working on some filesystem traversal code, I found myself
> > wanting to use the 'partition' function from Data.List, but with the
> > function 'doesDirectoryExist' in System.Directory (with type Filepath
> > -> IO Bool).  I noticed that there was no 'partitionM' in
> > Control.Monad, so I set out to write one.
> >
> > Here's what I ended up with:
> > > import Control.Monad (foldM)
> > >
> > > partitionMHelper :: Monad m => (a -> m Bool) -> ([a],[a]) -> a -> m
> > > ([a],[a])
>
> Before thinking much about it, I believe, a lazy pattern would help:
>
> partitionHelper p ~(ts,fs) x = do ...

First, typo, bad me.
Second, no it won't, we're doing a left fold (sort of), so it's already a good pair.

>
> The reverse in partitionM still forbids infinite lists, I'll come to that
> later.
>
> > > partitionMHelper p (ts,fs) x = do
> > >     b <- p x
> > >     return (if b then (x:ts,fs) else (ts,x:fs))
> > >
> > > partitionM :: (Monad m) => (a -> m Bool) -> [a] -> m ([a], [a])
> > > partitionM p xs = foldM (partitionMHelper p) ([],[]) $ reverse xs
> >
> > This works for my trivial cases, but can fail with extremely large
> > lists (not to mention being unable to take an infinite list and work
> > properly when passed to something like 'take 5').  

Can't, in general. What if some test at the end fails

(p x = [], resp Nothing, ioError (userError "too bad"))?

Then, for many monads the whole computation must fail, so you can't start returning 
anything before you know there is something to return.

> > Is there a way to change the function to avoid having to
> > traverse to the end of the list (via reverse) just to get the
> > output in the proper order?

Yes,

partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a],[a])
partitionM p xs = do
    (f,g) <- pMHelper p xs
    return (f [], g [])

pMHelper :: Monad m => (a -> m Bool) -> [a] -> m ([a] -> [a],[a] -> [a])
pMHelper p xs = foldM help (id,id) xs
      where
        help (f,g) x = do
            b <- p x
            return (if b then (f . (x:),g) else (f,g . (x:)))

It's a little slower than yours for my test, though and I don't see how to speed it up.

> > I started trying to write a "foldrM", 
> > but haven't gotten anywhere useful yet.
> >
> > Can someone point me in the right direction?




More information about the Beginners mailing list