[Haskell-cafe] Filtering a big list into the IO monad

Spencer Janssen spencerjanssen at gmail.com
Thu Aug 3 17:37:37 EDT 2006


This message is literate Haskell source.

> import System.IO.Unsafe (unsafeInterleaveIO)

First off, let's look at the code for filterM:

> filterM          :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
> filterM _ []     =  return []
> filterM p (x:xs) =  do
>    flg <- p x
>    ys  <- filterM p xs
>    return (if flg then x:ys else ys)

The potential for a stack overflow is pretty obvious here.  filterM is
applied to the tail of the list before any result is returned.

Here's a version that reverses the list as it filters.  It will run in
constant stack space.

> filterRevM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
> filterRevM p = flip go []
>  where go []     acc = return acc
>        go (x:xs) acc = do
>            flg <- p x
>            if flg
>                then go xs $! x:acc
>                else go xs acc

And finally, here's a version that uses unsafeInterleaveIO, and if it
isn't obvious, it really is unsafe!  Please read up on the risks of
unsafeInterleaveIO before using this version.

> unsafeFilterIO :: (a -> IO Bool) -> [a] -> IO [a]
> unsafeFilterIO p []     = return []
> unsafeFilterIO p (x:xs) = do
>     flg <- p x
>     ys  <- unsafeInterleaveIO $ unsafeFilterIO p xs
>     return (if flg then x:ys else ys)


Cheers,
Spencer Janssen


On 8/3/06, Gabriel Sztorc <lispozord at gmail.com> wrote:
| Hello,
|
| I want to filter a list with a predicate that returns a IO value,
| something that filterM is supposed to do. The problem is, filterM
| overflows the stack for really big lists and I couldn't come up with a
| simple replacement for filterM that would work for lists of any size
| (the truth is, I can't come up with anything at all :).
|
| The question is: how to do it? Any help is appreciated.
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
|


More information about the Haskell-Cafe mailing list