
Not a very descriptive subject, I know, but here's what I'd like to do. I can take getChar and create an infinate list: listChars = getChar : listChars but how do I go about creating a finite list, e.g. a list that ends as soon as 'q' is pressed? I was thinking of something like listChars1 = do c <- lift getChar if c == 'q' then [return c] else [return c] ++ listChars1 However, that triggers an interesting behaviour in ghci: *Main> :t listChars1 <interactive>:1:0: Can't find interface-file declaration for listChars1 Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error Compiling it doesn't work either: % ghc -o listio listio.hs listio.o: In function `Main_main_info': (.text+0x1bd): undefined reference to `Main_listChars1_closure' listio.o: In function `Main_main_srt': (.rodata+0x10): undefined reference to `Main_listChars1_closure' collect2: ld returned 1 exit status I was also looking briefly at ListT, bout couldn't quite see how to use basic list operations on it, e.g. ':' '++' etc. listChars2 :: ListT IO Char listChars2 = do c <- lift getChar if c == 'q' then lift $ return c else (lift $ return c) ++ listChars2 /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus Software is not manufactured, it is something you write and publish. Keep Europe free from software patents, we do not want censorship by patent law on written works. Microsoft has a new version out, Windows XP, which according to everybody is the 'most reliable Windows ever.' To me, this is like saying that asparagus is 'the most articulate vegetable ever.' -- Dave Barry

Magnus Therning wrote:
Not a very descriptive subject, I know, but here's what I'd like to do.
I can take getChar and create an infinate list:
listChars = getChar : listChars
but how do I go about creating a finite list, e.g. a list that ends as soon as 'q' is pressed?
I was thinking of something like
listChars1 = do c <- lift getChar if c == 'q' then [return c] else [return c] ++ listChars1
However, that triggers an interesting behaviour in ghci:

Oops, sorry, that should be: listChars2 :: ListT IO Char listChars2 = do c <- lift getChar if c == 'q' then return c else return c `mplus` listChars2

On 16/01/07, Yitzchak Gale
listChars2 :: ListT IO Char listChars2 = do c <- lift getChar if c == 'q' then return c else return c `mplus` listChars2
It's probably eaiser to work with normal lists: listChars :: IO [Char] listChars = do c <- getChar if c == 'q' then return c else liftM2 (:) (return c) listChars -- -David House, dmhouse@gmail.com

Hi, Am Dienstag, den 16.01.2007, 19:19 +0000 schrieb David House:
On 16/01/07, Yitzchak Gale
wrote: listChars2 :: ListT IO Char listChars2 = do c <- lift getChar if c == 'q' then return c else return c `mplus` listChars2
It's probably eaiser to work with normal lists:
listChars :: IO [Char] listChars = do c <- getChar if c == 'q' then return c else liftM2 (:) (return c) listChars
But that is not lazy any more, is it? The idea of the OT was, I think, that he can use the first elements of the list even before the last one was entered. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189

Hi,
It's probably eaiser to work with normal lists:
listChars :: IO [Char] listChars = do c <- getChar if c == 'q' then return c else liftM2 (:) (return c) listChars
But that is not lazy any more, is it? The idea of the OT was, I think, that he can use the first elements of the list even before the last one was entered.
But it's possible to make it lazy again using System.IO.Unsafe.unsafeInterleaveIO: listChars :: IO [Char] listChars = unsafeInterleaveIO $ do c <- getChar if c == 'q' then return c else liftM2 (:) (return c) listChars Regards, Martin.

On Tue, Jan 16, 2007 at 14:06:08 +0200, Yitzchak Gale wrote: [..]
But the list monad [] is not a transformer, so you can't lift in it, even if the contained type happens also to be a monad.
Yeah, I had some vague thought of that being a problem, which lead me to ListT. Your statement put some good words to that thought.
Perhaps you are looking for something like this, using the monad transformer version of []:
listChars2 :: ListT IO Char listChars2 = do c <- lift getChar if c == 'q' then return [c] else return [c] `mplus` listChars2
GHC finds this much more tasty, and then
runListT listChars2
does what I think you may want.
Yes, that is fairly close to what I want to do. Now, it'd be really good if I could apply a function to each item in the ListT, with the constraint that it should be done lazily. I.e. the following will not do runListT listChars2 >>= (mapM_ putChar) because it first reads the input until 'q' is pressed. I.e. this produces the interaction: abcqabcq What I want is the interaction: aabbccqq Hope you understand what I mean. /M P.S. I'm aware a reqursive solution is possible and I've already coded one that works. I'm just curious if a "map solution" is possible. -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

Try the code below. It is a fairly structured way to get exactly the behavior you asked for. The lazy and unsafeLazy versions are the ones you are interested in. module Main where import Data.Char import System.IO import System.IO.Unsafe newtype Stream a = Stream {next:: (IO (Maybe (a,Stream a)))} -- Run this "main" (e.g. in GHCI) and type several lines of text. -- The program ends when a line of text contains 'q' for the second time -- main = do hSetBuffering stdin NoBuffering hSetBuffering stdout NoBuffering print "Test of strict" opWith =<< strict untilQ print "Test of unsafeStrict" opWith $ unsafeStrict untilQ print "Test of lazy" opWith =<< lazy untilQ print "Test of unsafeLazy" opWith $ unsafeLazy untilQ -- Shorthand for test above. Processing the input through toUpper opWith = mapM_ print . lines . map toUpper untilQ :: Stream Char untilQ = Stream $ do c <- getChar if c == 'q' then return Nothing else return (Just (c,untilQ)) strict :: Stream a -> IO [a] strict s = do mc <- next s case mc of Nothing -> return [] Just (c,s') -> do rest <- strict s' return (c:rest) lazy :: Stream a -> IO [a] lazy s = unsafeInterleaveIO $ do mc <- next s case mc of Nothing -> return [] Just (c,s') -> do rest <- lazy s' return (c:rest) unsafeStrict :: Stream a -> [a] unsafeStrict s = unsafePerformIO (strict s) unsafeLazy :: Stream a -> [a] unsafeLazy s = unsafePerformIO (lazy s)

G'day all. On Tue, Jan 16, 2007 at 14:06:08 +0200, Yitzchak Gale wrote:
But the list monad [] is not a transformer, so you can't lift in it, even if the contained type happens also to be a monad.
Quoting Magnus Therning
Yeah, I had some vague thought of that being a problem, which lead me to ListT.
ListT is also not a transformer. See here for details: http://www.haskell.org/hawiki/ListTDoneRight Cheers, Andrew Bromage

I wrote:
But the list monad [] is not a transformer, so you can't lift in it, even if the contained type happens also to be a monad.
Andrew Bromage wrote:
ListT is also not a transformer.
True, unfortunately. But it does provide MonadTrans and MonadIO instances that solve problems like this in practice. What can be done to get an improved list transformer into MTL?
See here for details: http://www.haskell.org/hawiki/ListTDoneRight
Can someone with permissions on the new wiki please get this important page moved over? Thanks, Yitz

G'day all.
Quoting Yitzchak Gale
What can be done to get an improved list transformer into MTL?
Not sure. But a lot of people use mine: http://sigcomp.srmr.co.uk/~rjp/Nondet.hs (My darcs repository is down at the moment, unfortunately.) Cheers, Andrew Bromage

Hello Magnus, Tuesday, January 16, 2007, 2:34:51 PM, you wrote:
I can take getChar and create an infinate list:
listChars = getChar : listChars
but how do I go about creating a finite list, e.g. a list that ends as soon as 'q' is pressed?
you definitely should look into http://haskell.org/haskellwiki/IO_inside -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi, you can also try with unsafeInterleaveIO, works like a charm, and you really feel the laziness: *Main> main -- now entering “testq” t"teessttq" ======================== import System.IO.Unsafe sequence' :: [IO a] -> IO [a] sequence' (x:xs) = do r <- x; rs <- unsafeInterleaveIO (sequence' xs) return (r:rs) main = do allChars <- sequence' $ repeat getChar let getChars = takeWhile (/= 'q') allChars print getChars ======================== Unfortunately, this did not work: allChars <- sequence $ repeat $ unsafeInterleaveIO getChar Probably because of something sequence is doing. Greetings, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: joachimbreitner@amessage.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

Hi again, if sequence' should work with empty lists, then better write it like this: sequence' ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- unsafeInterleaveIO m'; return (x:xs) } Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: joachimbreitner@amessage.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

Thanks for all the excellent answers to my original question. Somehow it feels like I advanced and got one level closer to a black belt in Haskell due to this; I've now legitimately used a function from System.IO.Unsafe :-) I tried to document it all: http://therning.org/magnus/archives/249 /M http://liw.iki.fi/liw/log/2007-01.html#20070116b -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

Magnus Therning
Thanks for all the excellent answers to my original question. Somehow it feels like I advanced and got one level closer to a black belt in Haskell due to this; I've now legitimately used a function from System.IO.Unsafe :-)
I tried to document it all: http://therning.org/magnus/archives/249
I wonder whether the unsafeInterleaved solution is guarranteed to work as per your specification. Couldn't it read a character, write it, then read three characters, write two, read one more then write two again, and so on? It has to catch up at the end, but needn't stay synchronized during the process, perhaps... -- Thanks, Feri.

On Fri, Jan 19, 2007 at 11:19:16 +0100, Ferenc Wagner wrote:
Magnus Therning
writes: Thanks for all the excellent answers to my original question. Somehow it feels like I advanced and got one level closer to a black belt in Haskell due to this; I've now legitimately used a function from System.IO.Unsafe :-)
I tried to document it all: http://therning.org/magnus/archives/249
I wonder whether the unsafeInterleaved solution is guarranteed to work as per your specification. Couldn't it read a character, write it, then read three characters, write two, read one more then write two again, and so on? It has to catch up at the end, but needn't stay synchronized during the process, perhaps...
Good point! However, for my uses right now it doesn't matter. So rather than find a problem with the code you've found a problem with my requirements. Of course that's a good thing as well since you've helped me understand the problem better :-) /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

Hi, Am Freitag, den 19.01.2007, 11:19 +0100 schrieb Ferenc Wagner:
Magnus Therning
writes: Thanks for all the excellent answers to my original question. Somehow it feels like I advanced and got one level closer to a black belt in Haskell due to this; I've now legitimately used a function from System.IO.Unsafe :-)
I tried to document it all: http://therning.org/magnus/archives/249
I wonder whether the unsafeInterleaved solution is guarranteed to work as per your specification. Couldn't it read a character, write it, then read three characters, write two, read one more then write two again, and so on? It has to catch up at the end, but needn't stay synchronized during the process, perhaps...
I think it is: “unsafeInterleaveIO allows IO computation to be deferred lazily. When passed a value of type IO a, the IO will only be performed when the value of the a is demanded. This is used to implement lazy file reading, see hGetContents.”[1] If it would read a value that is not needed, it would violate the documented behaviour (the “only .. when .. demanded” is important). Greetings, Joachim [1] http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO-Unsafe.html... -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189

Magnus Therning asked:
but how do I go about creating a finite list, e.g. a list that ends as soon as 'q' is pressed?
A slightly different approach that doesn't use anything unsafe: What you want is to return something like an IO [Char] but it needs to be able to interleave IO. A list of type [Char] is essentially a solution to the equation X = Maybe (Char,X) It's either the empty list (represented by Nothing) or Just a pair of the head and tail of the list. But this doesn't allow us to intersperse IO along the computation of the list. In order to to that we need a solution to X = IO (Maybe (Char,X)) So define data X = X { unX :: IO (Maybe (Char,X)) } We can now write the 'q' terminated list as test = X $ do a <- getChar if a=='q' then return Nothing else return (Just (a,test)) For all intents and purposes, this is what you want. It reads characters until it reaches a 'q' and then returns IO Nothing. To make use of this we can write something like this to print out the contents of the list: test2 :: X -> IO () test2 test = do a <- unX test case a of Nothing -> return () Just (a,b) -> do print a test2 b 'test2 test' now prints out one of these q-terminated strings. There is a bit of clutter because of the X and unX. And it's slightly wordier because we're using Maybe instead of the nice Haskell List notation. But I think it does exactly what you want. In particular we have sepration of concerns - the object 'test' is in charge of generating data and test2 is responsible for reading it, without unsafe operations. And it seems to print the characters one at a time as they are entered (with ghc). -- Dan

Hi Dan, You have written a great explanation of how ListT works by writing out its definitions in an interesting way! Dan Piponi wrote:
A slightly different approach that doesn't use anything unsafe: A list of type [Char] is essentially a solution to the equation X = Maybe (Char,X)
Yes. In fact, the type data Y a = Y (Maybe (a, Y a)) is exactly equivalent to the type [a].
...to intersperse IO along the computation of the list... define data X = X { unX :: IO (Maybe (Char,X)) }
So that is exactly equivalent to the type ListT IO Char.
test = X $ do a <- getChar if a=='q' then return Nothing else return (Just (a,test))
That translates to: test = do a <- liftIO getChar guard $ a /= 'q' return $ a `mplus` test
test2 :: X -> IO () test2 test = do a <- unX test case a of Nothing -> return () Just (a,b) -> do print a test2 b
Translation: test2 = runListT . mapM (liftIO print) Regards, Yitz

On Tue, Jan 23, 2007 at 11:59:58 +0200, Yitzchak Gale wrote:
Hi Dan,
You have written a great explanation of how ListT works by writing out its definitions in an interesting way!
I assume you aren't talking about the standard ListT, the one that forces unnecessary strictness, right? But rather how ListT ought to be implemented. /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

On 1/23/07, Yitzchak Gale
You have written a great explanation of how ListT works by writing out its definitions in an interesting way!
I put quite a bit of time into understanding why the old ListT isn't a monad [1]. But I thought I didn't yet understand the new one. Now I see that I did, I just didn't know that I understood it! :-) -- Dan [1] http://sigfpe.blogspot.com/2006/11/why-isnt-listt-monad.html

I wrote:
You have written a great explanation of how ListT works by writing out its definitions in an interesting way!
Dan Piponi wrote:
I put quite a bit of time into understanding why the old ListT isn't a monad [1]. But I thought I didn't yet understand the new one. Now I see that I did, I just didn't know that I understood it! :-) [1] http://sigfpe.blogspot.com/2006/11/why-isnt-listt-monad.html
Hmm, I thought it was the old one...

Yitzchak,
Hmm, I thought it was the old one...
No, definitely the new one. The old one is: newtype ListT m a = ListT { runListT :: m [a] } which treats the entire list as one uninterleavable lump. The new one is: data MList' m a = MNil | a `MCons` MList m a type MList m a = m (MList' m a) newtype ListT m a = ListT { runListT :: MList m a } Note the definition of MList' is isomorphic to a use of Maybe. -- Dan

Dan Piponi wrote:
No, definitely the new one. The old one is:
newtype ListT m a = ListT { runListT :: m [a] }
which treats the entire list as one uninterleavable lump.
The new one is:
data MList' m a = MNil | a `MCons` MList m a type MList m a = m (MList' m a) newtype ListT m a = ListT { runListT :: MList m a }
OK.
Note the definition of MList' is isomorphic to a use of Maybe.
Yes, and in fact http://www.haskell.org/hawiki/ListTDoneRight_2fAlternative1 uses exactly your type. But the old broken ListT happens to work fine here. See my earlier post in this thread. Regards, Yitz

You are suggesting later in this thread that the old ListT could be used to solve my initial problem. I don't see how, so I'm wondering if you'd mind sorting some things out for me? On Tue, Jan 23, 2007 at 11:59:58 +0200, Yitzchak Gale wrote: [..]
test = do a <- liftIO getChar guard $ a /= 'q' return $ a `mplus` test
This piece has type problems. I couldn't get ghci to accept it without making some changes: test :: ListT IO Char test = do a <- liftIO getChar guard $ a /= 'q' (return a) `mplus` test [..]
test2 = runListT . mapM (liftIO print)
:t liftIO
:t print
There are some type problems here too, and I don't really see how to fix them. liftIO :: (MonadIO m) => IO a -> m a print :: (Show a) => a -> IO ()
:t (liftIO print) Couldn't match expected type `IO a' against inferred type `a1 -> IO ()' In the first argument of `liftIO', namely `print'
I also don't quite see how 'mapM foo` can be applied to a ListT since 'mapM foo' would have the type [a] -> m [b] (a & b depending on foo). Perhaps you didn't mean mapM but rather mapListT? But using mapListT in a similar way:
runListT.mapListT (\ m -> m >>= mapM putChar) $ test
does not result in the desired interleaving. Changing to using runListT first also gives the wrong behaviour:
runListT test >>= mapM_ putChar
I am really confused about your statement that ListT as found in GHC 6.6 can be used to solve my problem. I'd like to avoid using unsafeInterleaveIO if there's a nice solution for it. IMHO a solution with ListT would be nice, so I'd really like to understand how to make it work the way I want it. /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

Hi Magnus, You wrote:
This piece has type problems. I couldn't get ghci to accept it without making some changes...
You are absolutely correct, and I apologize for the errors. I will try one more time to give a corrected version below. Let me point out, though, that this does not exactly solve the problem you originally stated. Here is a summary and clarification of what we have come up with together so far: First, I said that it sounds like what you really want is ListT. But you pointed out that my ListT solution gave you the wrong order of interaction. The reason for this problem is a bug in the implementation of ListT in the standard libraries, which is explained on the wiki page: http://www.haskell.org/haskellwiki/ListT_done_right Dan Piponi posted a solution to your problem that works the way you want it, and without unsafeInterleaveIO. Dan's solution is just ListT in disguise, except that Dan used the corrected form of ListT like on the wiki page. My code in which you found the errors is a translation of Dan's solution back into ListT notation. So if you use that with the broken ListT currently in the standard libraries, you'll go back to the problem we had at the beginning. Here is the bottom line: You can solve your problem - without unsafeInterleaveIO - either by using one of the corrected versions of ListT listed on the wiki page, or by writing out an implementation of ListT that is hard-wired for your application like Dan did. OK, so here is my translation of Dan's code back into ListT notation again. I hope this version is now correct: test = do a <- liftIO getChar guard $ a /= 'q' return a `mplus` test test2 = (>>= liftIO . print) Run it with: runListT $ test2 test Note that you probably want putChar instead of print. Also, Dan's version drops the 'q' at the end, while your code prints the 'q'. Hope this helps. Regards, Yitz

Thanks for an excellent clarification. I have been known to be rather daft at times so I just wanted to make sure I understood everything correctly. Thanks! /M On Sun, Jan 28, 2007 at 12:56:56 +0200, Yitzchak Gale wrote:
Hi Magnus,
You wrote:
This piece has type problems. I couldn't get ghci to accept it without making some changes...
You are absolutely correct, and I apologize for the errors. I will try one more time to give a corrected version below.
Let me point out, though, that this does not exactly solve the problem you originally stated. Here is a summary and clarification of what we have come up with together so far:
First, I said that it sounds like what you really want is ListT.
But you pointed out that my ListT solution gave you the wrong order of interaction.
The reason for this problem is a bug in the implementation of ListT in the standard libraries, which is explained on the wiki page:
http://www.haskell.org/haskellwiki/ListT_done_right
Dan Piponi posted a solution to your problem that works the way you want it, and without unsafeInterleaveIO. Dan's solution is just ListT in disguise, except that Dan used the corrected form of ListT like on the wiki page.
My code in which you found the errors is a translation of Dan's solution back into ListT notation. So if you use that with the broken ListT currently in the standard libraries, you'll go back to the problem we had at the beginning.
Here is the bottom line:
You can solve your problem - without unsafeInterleaveIO - either by using one of the corrected versions of ListT listed on the wiki page, or by writing out an implementation of ListT that is hard-wired for your application like Dan did.
OK, so here is my translation of Dan's code back into ListT notation again. I hope this version is now correct:
test = do a <- liftIO getChar guard $ a /= 'q' return a `mplus` test
test2 = (>>= liftIO . print)
Run it with:
runListT $ test2 test
Note that you probably want putChar instead of print. Also, Dan's version drops the 'q' at the end, while your code prints the 'q'.
Hope this helps.
Regards, Yitz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus
participants (10)
-
ajb@spamcop.net
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Dan Piponi
-
David House
-
Ferenc Wagner
-
Joachim Breitner
-
Magnus Therning
-
Martin Huschenbett
-
Yitzchak Gale