Re: [Haskell-cafe] IO in lists

2007-01-19 Thread 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

/M

http://liw.iki.fi/liw/log/2007-01.html#20070116b

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus


pgpZG9AiJbjF8.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-17 Thread Yitzchak Gale

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-17 Thread ajb
G'day all.

Quoting Yitzchak Gale [EMAIL PROTECTED]:

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IO in lists

2007-01-16 Thread Magnus Therning
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)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
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


pgpkXwPGUdFS3.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Yitzchak Gale

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:


GHC's impolite choking noises deleted

You are trying to define something of type [IO Char].

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.

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.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Yitzchak Gale

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Magnus Therning
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)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus


pgpkBnPyR98zZ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Bulat Ziganshin
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,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Joachim Breitner
Hi,

you can also try with unsafeInterleaveIO, works like a charm, and you
really feel the laziness:

*Main main
-- now entering “testq”
tteessttq


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: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Joachim Breitner
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: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread David House

On 16/01/07, Yitzchak Gale [EMAIL PROTECTED] 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

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Joachim Breitner
Hi,

Am Dienstag, den 16.01.2007, 19:19 + schrieb David House:
 On 16/01/07, Yitzchak Gale [EMAIL PROTECTED] 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: [EMAIL PROTECTED]
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread Chris Kuklewicz
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)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO in lists

2007-01-16 Thread ajb
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 [EMAIL PROTECTED]:

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe