Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

iterate list creation from IO Int, How to?

I am playing with linkedlist problem in python challenge that require querying a next value (guess it be Int).

I create function for get the next value as follows

url = "http://www.pythonchallenge.com/pc/def/linkedlist.php?nothing=" 

getNext :: Int -> IO Int
getNext x = do
    rsp <- simpleHTTP (getRequest $ url ++ show x)
    bdy <- getResponseBody rsp
    let num = last $ splitWhen (==' ') bdy
    return (read num::Int)

and it work fine (in ghci)

> getNext 12345
44827
> getNext 44827
45439

While I suppose to repeatedly call getNext until I found the answer, I think I should keep the history like I can do in non-monadic world so I can continue from the last value in case something fail.

> let nX x = x + 3
> :t nX
nX :: Num a => a -> a
> take 10 $ iterate nX 1
[1,4,7,10,13,16,19,22,25,28]

I think it should be a monadic lifted version of iterate and found iterateM_ from Control.Monad.Loops but it didn't work as I expected. There is nothing shown (I think _ suffix mean discard the result but there is no iterateM)

> :t iterate
iterate :: (a -> a) -> a -> [a]
> :t iterateM_
iterateM_ :: Monad m => (a -> m a) -> a -> m b

Question is how can I get [Int] as in non-monadic iteration. I think I want a function that return IO [Int] to be able to pull-out and filter/process in my code like this

main = do
    i <- getAllList
    let answer = last i -- or could be a repeated converged value, don't know yet
    putStrLn (show answer)

getAllList :: IO [Int]
like image 264
wizzup Avatar asked Feb 06 '13 14:02

wizzup


2 Answers

If you want your function to terminate early, rather than give back an infinite list of results, you will want to use unfoldrM rather than iterateM. This can be done with something like the following:

url = "http://www.pythonchallenge.com/pc/def/linkedlist.php?nothing=" 


start = 12345
stop  = 10000

shouldStop :: Int -> Bool
shouldStop x = x == stop

getNext :: Int -> IO (Maybe (Int, Int))
getNext prev
    | shouldStop prev = return Nothing
    | otherwise       = do
        rsp <- simpleHTTP (getRequest $ url ++ show prev)
        bdy <- getResponseBody rsp
        let num = read $ last $ splitWhen (==' ') bdy :: Int
        print (prev, num)
        return $ Just (num, num)

getAllList :: IO [Int]
getAllList = unfoldrM getNext start

This will allow you to define a stopping criteria so that the loop can terminate, but you will not receive results back until the termination criteria has been met.

The unfoldrM function can be found in the monad-loops package, but the latest version keeps reusing the original seed rather than the one produced by the generator function (I believe this has been fixed but not uploaded to Hackage). This is the version of unfoldrM that you would want.

-- |See 'Data.List.unfoldr'.  This is a monad-friendly version of that.
unfoldrM :: (Monad m) => (a -> m (Maybe (b,a))) -> a -> m [b]
unfoldrM = unfoldrM'

-- |See 'Data.List.unfoldr'.  This is a monad-friendly version of that, with a
-- twist.  Rather than returning a list, it returns any MonadPlus type of your
-- choice.
unfoldrM' :: (Monad m, MonadPlus f) => (a -> m (Maybe (b,a))) -> a -> m (f b)
unfoldrM' f z = go z
    where go z = do
            x <- f z
            case x of
                Nothing         -> return mzero
                Just (x, z)     -> do
                        xs <- go z
                        return (return x `mplus` xs)

This is how you might go about this using Pipes, which will allow you to do the processing as a stream of results without resorting to lazy I/O.

import Network.HTTP
import Control.Monad
import Data.List.Split
import Control.Monad
import Control.Proxy

url = "http://www.pythonchallenge.com/pc/def/linkedlist.php?nothing="

grabber :: (Proxy p) => Int -> () -> Producer p String IO ()
grabber start () = runIdentityP $ loop $ show start where
    loop x = do
        -- Grab the next value
        x' <- lift $ getNext x
        -- Send it down stream
        respond x'
        -- Keep grabbing
        loop x'

-- Just prints the values recieved from up stream
printer :: (Proxy p, Show a) => () -> Consumer p a IO r
printer () = runIdentityP $ forever $ do
    a <- request ()  -- Consume a value
    lift $ putStrLn $ "Received a value: " ++ show a

getNext :: String -> IO String
getNext prev = do
    rsp <- simpleHTTP (getRequest $ url ++ prev)
    bdy <- getResponseBody rsp
    let num  = last $ splitWhen (== ' ') bdy
    return num

main = runProxy $ grabber start >-> printer
like image 134
sabauma Avatar answered Nov 02 '22 10:11

sabauma


So what you want is basically

iterateM :: Monad m => (a -> m a) -> a -> m [a]
iterateM action a = do
   a' <- action a
   liftM (a':) $ iterateM action a'

The problem is that this doesn't work lazily as one might expect: since the monadic bind is strict, you're stuck in an infinite loop, even if you only want to evaluate a finite number of as.

like image 44
leftaroundabout Avatar answered Nov 02 '22 10:11

leftaroundabout