Hi,

GHC's behaviour is consistent with the report, Hugs' isn't.
This issue came up on the haskell mailing list a couple of months ago,
see 

 http://www.dcs.gla.ac.uk/mail-www/haskell/threads#00270

for more info.

hth,
--Sigbjorn

David Barton writes:
> Consider the following (literate) program:
> 
> > module Main where
> > import IO
> 
> > main:: IO()
> > main = hSetBuffering stdin NoBuffering  >>
> >        interact trns
> 
> > trns:: String -> String
> > trns []     = []
> > trns (c:cs) = 
> >   let str c = case c of
> >                 '1' -> "one\n"
> >                 '2' -> "two\n"
> >                 '3' -> "three\n"
> >                 _   -> "other\n"
> >   in (str c) ++ (trns cs)
> 
> This compiles under both Hugs and GHC appropriately (note that I added
> a blank "hSetBuffering" defintion to IO.hs for Hugs).  When I run the
> program under Hugs and enter press the keys "1234" on the keyboard I
> get the following output:
> 
> one
> two
> three
> other
> 
> which is just what I expect.  On the other hand, when I try it under
> GHC it compiles appropriately and I get the following output:
> 
> 1one
> 2two
> 3three
> 4other
> 
> i.e. the input is somehow echoed to stdout without my trying to do
> anything.  Is this a Unix thing?  If so, why didn't it happen under
> Hugs?  Is it a GHC thing?  Is it controllable?  If so, how can I stop
> it?
> 
> Any help gratefully appreciated.
> 
>                                       Dave Barton <*>
>                                       [EMAIL PROTECTED] )0(
>                                       http://www.intermetrics.com/~dlb

Reply via email to