views:

688

answers:

4

I have some functions written in C that I call from Haskell. These functions return IO (CInt). Sometimes I want to run all of the functions regardless of what any of them return, and this is easy. For sake of example code, this is the general idea of what's happening currently:

Prelude> let f x = print x >> return x
Prelude> mapM_ f [0..5]
0
1
2
3
4
5
Prelude>

I get my desired side effects, and I don't care about the results. But now I need to stop execution immediately after the first item that doesn't return my desired result. Let's say a return value of 4 or higher requires execution to stop - then what I want to do is this:

Prelude> takeWhile (<4) $ mapM f [0..5]

Which gives me this error:

<interactive>:1:22:
    Couldn't match expected type `[b]' against inferred type `IO a'
    In the first argument of `mapM', namely `f'
    In the second argument of `($)', namely `mapM f ([0 .. 5])'
    In the expression: takeWhile (< 4) $ mapM f ([0 .. 5])

And that makes sense to me - the result is still contained in the IO monad, and I can't just compare two values contained in the IO monad. I know this is precisely the purpose of monads -- chaining results together and discarding operations when a certain condition is met -- but is there an easy way to "wrap up" the IO monad in this case to stop executing the chain upon a condition of my choosing, without writing an instance of MonadPlus?

Can I just "unlift" the values from f, for the purposes of the takeWhile?

Is this a solution where functors fit? Functors haven't "clicked" with me yet, but I sort of have the impression that this might be a good situation to use them.


Update:

@sth has the closest answer to what I want - in fact, that's almost exactly what I was going for, but I'd still like to see whether there is a standard solution that isn't explicitly recursive -- this is Haskell, after all! Looking back on how I worded my question, now I can see that I wasn't clear enough about my desired behavior.

The f function I used above for an example was merely an example. The real functions are written in C and used exclusively for their side effects. I can't use @Tom's suggestion of mapM_ f (takeWhile (&lt;4) [0..5]) because I have no idea whether any input will really result in success or failure until executed.

I don't actually care about the returned list, either -- I just want to call the C functions until either the list is exhausted or the first C function returns a failure code.

In C-style pseudocode, my behavior would be:

do {
    result = function_with_side_effects(input_list[index++]);
} while (result == success && index < max_index);

So again, @sth's answer performs the exact behavior that I want, except that the results may (should?) be discarded. A dropWhileM_ function would be equivalent for my purposes. Why isn't there a function like that or takeWhileM_ in Control.Monad? I see that there was a similar discussion on a mailing list, but it appears that nothing has come of that.

+9  A: 

Edit: Now I see what you're looking for.

gbacon posted a nice sequenceWhile function, which is almost the "primitive" you need.

Actually, since you're only interested in the side effects, sequenceWhile_ should be enough. Here's a definition (again, inspired by gbacon, vote him up!):

sequenceWhile_ :: (Monad m) => (a -> Bool) -> [m a] -> m ()
sequenceWhile_ p xs = foldr (\mx my -> mx >>= \x -> when (p x) my)
                            (return ()) xs

You call this like so:

Prelude Control.Monad> sequenceWhile (<4) $ map f [1..]


Original answer:

You can't just "unlift" the values from the IO Monad for use with takeWile, but you can "lift" takeWhile for use within a Monad!

The liftM function will take a function (a -> b) to a function (m a -> m b), where m is a Monad.

(As a side note, you can find a function like this by searching for its type on Hoogle, in this case by searching for: Monad m => (a -> b) -> (m a -> m b))

With liftM you can do this:

Prelude> :m + Control.Monad
Prelude Control.Monad> let f x = print x >> return x
Prelude Control.Monad> liftM (takeWhile (<4)) $ mapM f [0..5]
0
1
2
3
4
5
[0,1,2,3]

Now, this might not be what you wanted. The mapM will apply the f function to the entire list in sequence, before returning a list. That resulting list is then passed to the lifted takeWhile function.

If you want to stop printing after the third element, you'll have to stop calling print. That means, don't apply f to such an element. So, you'll end up with something simple like:

Prelude> mapM_ f (takeWhile (<4) [0..5])


By the way, should you wonder why mapM will first print everything, before returning the list. You can see this by replacing the functions with their definitions:

mapM f [0..1]
=
sequence (map f [0..1])
=
sequence (f 0 : map f [1..1])
=
sequence (f 0 : f 1 : [])
=
sequence ((print 0 >> return 0) : f 1 : [])
= 
sequence ((print 0 >> return 0) : (print 1 >> return 1) : [])
=
do x  <- (print 0 >> return 0)
   xs <- (sequence ((print 1 >> return 1) : []))
   return (x:xs)
=
do x  <- (print 0 >> return 0)
   xs <- (do y  <- (print 1 >> return 1)
             ys <- sequence ([])
             return (y:ys))
   return (x:xs)
=
do x  <- (print 0 >> return 0)
   xs <- (do y  <- (print 1 >> return 1)
             ys <- return []
             return (y:ys))
   return (x:xs)
=
do x  <- (print 0 >> return 0)
   xs <- (do y <- (print 1 >> return 1)
             return (y:[]))
   return (x:xs)
=
do x  <- (print 0 >> return 0)
   xs <- (print 1 >> return (1:[]))
   return (x:xs)
=
do x <- (print 0 >> return 0)
   print 1
   return (x:1:[])
=
do print 0
   print 1
   return (0:1:[])

This process of replacing functions with their definitions is called equational reasoning.

If I didn't make any mistakes, you can now (hopefully) see that mapM (using sequence) first prints everything, and then returns a list.

Tom Lokhorst
That wasn't the real behavior I wanted, but +1 for a good explanation. liftM makes a lot more sense now.
Mark Rushakoff
+12  A: 

I don't think there is anything like a takeWhileM in the standard library, but you could write it yourself so that only as much IO as needed is executed:

takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
takeWhileM _ [] = return []
takeWhileM p (a:as) =
   do v <- a
      if p v
         then do vs <- takeWhileM p as
                 return (v:vs)
         else return []

The supplied list is only evaluated until an element is found, that doesn't match the predicate:

*Main> takeWhileM (<4) (map f [1..5])
1
2
3
4
[1,2,3]
sth
For consistency with `Control.Monad.filterM`, I'd expect a type more like `takeWhileM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]`; that would make the usage something like `join . liftM sequence . takeWhileM (liftM (< 4))`. But that's quite a bit uglier for what OP wants, so meh.
ephemient
@sth, @ephemient: not in the standard library, but in my newly released "generator" package (in hackage) there's a more general takeWhile function. your takeWhileM needs the list of actions to not depend on actions inside the monad, while generator's takeWhile gets a List whose monad is m, allowing for the same and more.
yairchu
+1 for exactly matching the behavior I wanted. I updated the question, and I'm going to wait and see if anyone has a standard lib solution. If there isn't one, I'm accepting your answer.
Mark Rushakoff
+4  A: 

You can use the one from the "List" package.

import Control.Monad.ListT (ListT)
import Data.List.Class (execute, fromList, joinM, takeWhile)
import Prelude hiding (takeWhile)

f x = print x >> return x
main =
  execute . takeWhile (< 4) .
  joinM $ fmap f (fromList [0..5] :: ListT IO Int)
  • fromList [0..5] creates a monadic list containing 0..5 which performs no monadic actions
  • fmap f to that list results in a ListT IO (IO Int) which still performs no monadic actions, just contains ones.
  • joinM turns that into a ListT IO Int. every contained action would get executed when the item is consumed and its result will be the value in the list.
  • takeWhile is generalized for any List. Both [] and "Monad m => ListT m" are instances of List.
  • execute consumes the monadic list, executing all its actions.
  • In case you are interested in the results you can use "toList :: List m => m a -> ItemM m [a]" ("ItemM (ListT IO)" is IO). so in this case it's "toList :: ListT IO a -> IO [a]". Better yet you can keep using higher-order functions such as scanl, etc to process the monadic list as it is being executed.
yairchu
+7  A: 

You might define sequence as

sequence xs = foldr (liftM2 (:)) (return []) xs

The problem with liftM2 that you've been seeing is you don't have an opportunity to stop m2, which might be launchTheMissiles!

liftM2 :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c
liftM2 f m1 m2 = do
    x1 <- m1
    x2 <- m2
    return (f x1 x2)

Using guard as in the following seems appealing:

sequenceUntil p xs = foldr (myLiftM2 p (:)) (return []) xs
  where myLiftM2 p f m1 m2 = do
            x1 <- m1
            guard $ p x1
            x2 <- m2
            return (f x1 x2)

The code above will fail in your application because the IO monad is not an instance of MonadPlus.

So hold its hand a little more

module Main where

import Control.Monad

printx :: Int -> IO Int
printx x = do
    print x
    return x

sequenceUntil :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
sequenceUntil p xs = foldr (myLiftM2 (:) []) (return []) xs
  where myLiftM2 f z m1 m2 = do
            x1 <- m1
            if p x1 then do x2 <- m2
                            return $ f x1 x2
                    else return z

main :: IO ()
main = do
  let as :: [IO Int]
      as = map printx [1..10]
  ys <- sequenceUntil (< 4) as
  print ys

Even though as is a list of actions over 1 to 10, the output is

1
2
3
4
[1,2,3]

Discarding the results is then trivial:

sequenceUntil_ :: (Monad m) => (a -> Bool) -> [m a] -> m ()
sequenceUntil_ p xs = sequenceUntil p xs >> return ()

main :: IO ()
main = do
  let as :: [IO Int]
      as = map printx [1..]
  sequenceUntil_ (< 4) as

Note the use of [1..] that shows the new combinator maintains laziness.


You may prefer spanM:

spanM :: (Monad m) => (a -> Bool) -> [m a] -> m ([a], [m a])
spanM _ [] = return ([], [])
spanM p (a:as) = do
  x <- a
  if p x then do (xs,bs) <- spanM p as
                 return (x:xs, bs)
         else return ([x], as)

Note that it differs slightly from span in that it includes the failing element in the result list. The pair's second is the remaining actions. For example:

*Main> (xs,bs) <- spanM (< 4) as
1
2
3
4
*Main> xs  
[1,2,3,4]
*Main> sequence bs
5
6
7
8
9
10
[5,6,7,8,9,10]


Yet another alternative:

untilM :: Monad m => (a -> Bool) -> [m a] -> m ()
untilM p (x:xs) = do
  y <- x
  unless (p y) $ untilM p xs

Note that the sense of the predicate is complemented:

*Main> untilM (>= 4) as
1
2
3
4
Greg Bacon
+1, nice definition of `sequenceWhile`. I was first trying to define it using `foldM` instead of `foldr`, but that obviously won't work, since that still forces the entire list.
Tom Lokhorst
Someone suggested a better name: sequenceUntil. I also added spanM as an alternative.
Greg Bacon