How do I handle an infinite list of IO objects in Haskell?

Up vote 7 down vote favorite 2 share g+ share fb share tw.

I'm writing a program that reads from a list of files. The each file either contains a link to the next file or marks that it's the end of the chain. Being new to Haskell, it seemed like the idiomatic way to handle this is is a lazy list of possible files to this end, I have getFirstFile :: String -> DataFile getNextFile :: Maybe DataFile -> Maybe DataFile loadFiles :: String -> Maybe DataFile loadFiles = iterate getNextFile .

Just . GetFirstFile getFiles :: String -> DataFile getFiles = map fromJust . TakeWhile isJust .

LoadFiles So far, so good. The only problem is that, since getFirstFile and getNextFile both need to open files, I need their results to be in the IO monad. This gives the modified form of getFirstFile :: String -> IO DataFile getNextFile :: Maybe DataFile -> IO (Maybe DataFile) loadFiles :: String -> IO Maybe DataFile loadFiles = iterate (getNextFile = IO DataFile getFiles = liftM (map fromJust .

TakeWhile isJust) . Sequence . LoadFiles The problem with this is that, since iterate returns an infinite list, sequence becomes an infinite loop.

I'm not sure how to proceed from here. Is there a lazier form of sequence that won't hit all of the list elements? Should I be rejiggering the map and takeWhile to be operating inside the IO monad for each list element?

Or do I need to drop the whole infinite list process and write a recursive function to terminate the list manually? Haskell io monads infinite-loop lazy-evaluation link|improve this question edited Oct 11 '11 at 23:57trinithis3,6271121 asked Oct 11 '11 at 22:53user640078774.

A step in the right direction What puzzles me is getNextFile. Step into a simplified world with me, where we're not dealing with IO yet. The type is Maybe DataFile -> Maybe DataFile.

In my opinion, this should simply be DataFile -> Maybe DataFile, and I will operate under the assumption that this adjustment is possible. And that looks like a good candidate for unfoldr. The first thing I am going to do is make my own simplified version of unfoldr, which is less general but simpler to use. Import Data.

List -- unfoldr :: (b -> Maybe (a,b)) -> be -> a myUnfoldr :: (a -> Maybe a) -> a -> a myUnfoldr f v = v : unfoldr (fmap tuplefy . F) v where tuplefy x = (x,x) Now the type f :: a -> Maybe a matches getNextFile :: DataFile -> Maybe DataFile getFiles :: String -> DataFile getFiles = myUnfoldr getNextFile . GetFirstFile Beautiful, right?

Unfoldr is a lot like iterate, except once it hits Nothing, it terminates the list. Now, we have a problem. IO.

How can we do the same thing with IO thrown in there? Don't even think about The Function Which Shall Not Be Named. We need a beefed up unfoldr to handle this.

Fortunately, the source for unfoldr is available to us. Unfoldr :: (b -> Maybe (a, b)) -> be -> a unfoldr f be = case f be of Just (a,new_b) -> a : unfoldr f new_b Nothing -> Now what do we need? A healthy dose of IO.

LiftM2 unfoldr almost gets us the right type, but won't quite cut it this time. An actual solution unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> be -> m a unfoldrM f be = do res do bs return It is a rather straightforward transformation; I wonder if there is some combinator that could accomplish the same. Fun fact: we can now define unfoldr f be = runIdentity $ unfoldrM (return .

F) be Let's again define a simplified myUnfoldrM, we just have to sprinkle in a liftM in there: myUnfoldrM :: Monad m => (a -> m (Maybe a)) -> a -> m a myUnfoldrM f v = (v:) `liftM` unfoldrM (liftM (fmap tuplefy) . F) v where tuplefy x = (x,x) And now we're all set, just like before. GetFirstFile :: String -> IO DataFile getNextFile :: DataFile -> IO (Maybe DataFile) getFiles :: String -> IO DataFile getFiles str = do firstFile IO DataFile getFiles' = myUnfoldrM getNextFile a -> Maybe a collatz 1 = Nothing -- the sequence ends when you hit 1 collatz n | even n = Just $ n `div` 2 | otherwise = Just $ 3 * n + 1 collatzSequence :: Integral a => a -> a collatzSequence = myUnfoldr collatz Remember, myUnfoldr is a simplified unfold for the cases where the "next seed" and the "current output value" are the same, as is the case for collatz.

This behavior should be easy to see given myUnfoldr's simple definition in terms of unfoldr and tuplefy x = (x,x). Ghci> collatzSequence 9 9,28,14,7,22,11,34,17,52,26,13,40,20,10,5,16,8,4,2,1 More, mostly unrelated thoughts The rest has absolutely nothing to do with the question, but I just couldn't resist musing. We can define myUnfoldr in terms of myUnfoldrM: myUnfoldr f v = runIdentity $ myUnfoldrM (return .

F) v Look familiar? We can even abstract this pattern: sinkM :: ((a -> Identity b) -> a -> Identity c) -> (a -> b) -> a -> c sinkM hof f = runIdentity . Hof (return .

F) unfoldr = sinkM unfoldrM myUnfoldr = sinkM myUnfoldrM sinkM should work to "sink" (opposite of "lift") any function of the form Monad m => (a -> m b) -> a -> m c. Since the Monad m in those functions can be unified with the Identity monad constraint of sinkM. However, I don't see anything that sinkM would actually be useful for.

Yes, this answer cures the disease instead of just treating the symptoms! – pat Oct 12 '11 at 14:46 Important to note: myUnfoldr and myUnfoldrM will not keep the first file in the list; it is simply considered the seed to produce the rest of the list. This could easily be remedied if need be.

– Dan Burton Oct 12 '11 at 15:11 1 I couldn't find a combinator for unfoldM but I did manage to turn it into this totally incomprehensible one-liner: unfoldrM f = (>>= maybe (return ) (uncurry $ \a -> liftM (a:) . UnfoldrM f)) . F – pat Oct 12 '11 at 15:25 1 Since (Identity.

) and (runIdentity. ) convert between a -> Identity be and a -> be you can write sinkM f = (runIdentity. ) .

F . (Identity. ).

Also note sinkM mapM = map, sinkM filterM = filter. – sdcvvc Oct 12 '11 at 12:27 @sdcvvc Very cool, thanks for noticing! Interesting to note that the type signature I wrote for sinkM is too restrictive to use it for those.

It should instead be ((a -> Identity b) -> a1 -> Identity c) -> (a -> b) -> a1 -> c. In fact, using return instead of Identity, it is inferred to be even more generic. – Dan Burton Oct 12 '11 at 2:45.

SequenceWhile :: Monad m => (a -> Bool) -> m a -> m a sequenceWhile _ = return sequenceWhile p (m:ms) = do x.

Trying to google for takeWhileM, I have found a related question with code almost identical to yours: stackoverflow.com/questions/1133800/hask... – Rotsor Oct 12 '11 at 3:45 Haha, speaking of which, I recently added the monadlist package to hackage. It has a takeWhileM with (a -> m a) -> a -> m a (well, more general with MonadPlus return value). I'm going to have to add my sequenceWhile function in there and a sequenceWhileM (a -> m Bool).

– trinithis Oct 12 '11 at 4:53.

As you have noticed, IO results can't be lazy, so you can't (easily) build an infinite list using IO. There is a way out, however, in unsafeInterleaveIO; with this, you can do something like: ioList startFile = do v >= ioList) return (v:continuation) It's important to be careful here, though - you've just deferred the results of ioList to some unpredictable time in the future. It may never be run at all, in fact.

So be very careful when you're being Clever™ like this. Personally, I would just build a manual recursive function.

3 +1 for a good answer and especially for »clever™« – FUZxxl Oct 11 '11 at 23:01.

Laziness and I/O are a tricky combination. Using unsafeInterleaveIO is one way to produce lazy lists in the IO monad (and this is the technique used by the standard getContents, readFile and friends). However, as convenient as this is, it exposes pure code to possible I/O errors and makes makes releasing resources (such as file handles) non-deterministic.

This is why most "serious" Haskell applications (especially those concerned with efficiency) nowadays use things called Enumerators and Iteratees for streaming I/O. One library in Hackage that implements this concept is enumerator. You are probably fine with using lazy I/O in your application, but I thought I'd still give this as an example of another way to approach these kind of problems.

You can find more in-depth tutorials about iteratees here and here. For example, your stream of DataFiles could be implemented as an Enumerator like this: import Data. Enumerator import Control.Monad.IO.

Class (liftIO) iterFiles :: String -> Enumerator DataFile IO be iterFiles s = first where first (Continue k) = do file >== next file first step = returnI step next prev (Continue k) = do file k EOF Just df -> k (Chunks df) >>== next df next _ step = returnI step.

I cant really gove you an answer,but what I can give you is a way to a solution, that is you have to find the anglde that you relate to or peaks your interest. A good paper is one that people get drawn into because it reaches them ln some way.As for me WW11 to me, I think of the holocaust and the effect it had on the survivors, their families and those who stood by and did nothing until it was too late.

Related Questions