Re: "interact" behaves oddly if used interactively

2003-10-01 Thread b . i . mills
On the pedagogic part of this issue, I personally feel that using interact 
causes concentration on the temporal logic aspects of the code. That is, 
on understanding the interaction between the computer and the user as a 
whole. Although the monad approach has this in it, I feel it to be more 
hidden, and I like my students to have some experience with interact 
before going any significant distance into monadic IO. Similarly, I like
them to look at other monads before IO monads, and IO monads before trying
the do constructs. I've found that without the background of monads, the
students get into tangles with the seemingly strange logic of the construct,
and the error messages don't help them at all.

However, on the down side of interact, I do have a grumble.

I like to use the exercise of writing a generic command line
processor, with line editing capacity as the basic task. The
answer I'm looking for is just something like ...

parse = lines

execute s = if s==endCode then "" else "{" ++ s ++ "}"

endCode = "stop"

fini a = (take (length endCode) a) == endCode

del ('\27':'\91':'\51':'\126':t) = True
del _ = False

edit s = aux 0 s [] where
 aux n [] b = '\n' : (blat (reverse b))
 aux 0 b c | del b = aux 0 (drop 4 b) c
 aux n b (x:c) | del b = '\b' : ' ' : '\b' : (aux (n-1) (drop 4 b) c)
 aux n (a:b) c = a : (aux (n+1) b (a : c))

join (a:b) = a ++ "\n" ++ (if (fini a) then [] else "cmd: " ++ (join b))

blat s = execute (head (parse s))

myCmd = interact (\s -> "cmd: " ++ (join (map edit (lines s

In this code ... look at join, we could write this more along
the lines of ...

join ("stop\n":b) = "stop\n"
join (a:b) = a ++ "\ncmd: " ++ (join b)

But this basic approach has the problem (at least under Hugs) that 
when we enter the word "stop" at the command prompt, the word will 
not be echoed until we have got past the p in stop. But, it does 
not matter which line code we take, the initial characters of the 
string are the same. 

Although it is a tall order to work this out in general, it does
seem to be fairly obvious in this case. That is, if I feed in something
of the form ('s':b), then I can see that under each clause I must 
irrevocably get something of the form ('s':t) back, and further more
if the first clause does not in the end match, then the second one
will anyway (since we already know we have a list of at least one
character). So, it is apparent at this stage that the output will
not be an error (the only way that join has started processing this
is that it was successfully returned by edit as a complete string), 
and will start with an 's'.

Would such a characteristic make it easier or harder to work 
with interact?

Just a thought,

Bruce,

Institute for Information and Mathematical Sciences
Massey University at Albany, New Zealand.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


exitImmediately's signature

2003-10-01 Thread Dean Herington
Is there a good reason why `exitImmediately` (in System.Posix.Process as 
well as other places) shouldn't return `IO a` instead of `IO ()`?


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Christian Maeder
Can actually someone supply an implementation of something like interact 
that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
!$ s" was not enough!
Yes, of course.

Your code above only forces the evaluation of the first cons-cell of
the list, which is not enough.  You want to force the entire list.
Right, thanks to everybody who provided solutions!

Christian

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Dean Herington
On Wed, 1 Oct 2003, Keith Wansbrough wrote:

> > Can actually someone supply an implementation of something like interact 
> > that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
> > !$ s" was not enough!
> 
> Yes, of course.
> 
> Your code above only forces the evaluation of the first cons-cell of
> the list, which is not enough.  You want to force the entire list.
> Try
> 
> deepSeq :: [a] -> b -> b
> deepSeq (x:xs) y = deepSeq xs y
> deepSeq [] y = y
> 
> noninteract f = do
>   s <- getContents
>   putStr (f (deepSeq s s))


Here's another way to write the above:

import DeepSeq
noninteract f = getContents >>= (putStr . f $!!)

-- Dean


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Keith Wansbrough
> Allow me to have another opinion, if the consequence is interleaved in- 
> and output (when I don't want it).
> 
> Can actually someone supply an implementation of something like interact 
> that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
> !$ s" was not enough!

Yes, of course.

Your code above only forces the evaluation of the first cons-cell of
the list, which is not enough.  You want to force the entire list.
Try

deepSeq :: [a] -> b -> b
deepSeq (x:xs) y = deepSeq xs y
deepSeq [] y = y

noninteract f = do
  s <- getContents
  putStr (f (deepSeq s s))

or if you want non-lazy output too,

reallynoninteract f = do
  s <- get Contents
  let r = f (deepSeq s s)
  putStr (deepSeq r r)

untested code!

There's a library containing such functions, called (IIRC) DeepSeq or
something similar.

HTH.

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Tomasz Zielonka
On Wed, Oct 01, 2003 at 04:42:51PM +0200, Christian Maeder wrote:
> Can actually someone supply an implementation of something like interact 
> that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
> !$ s" was not enough!

The simplest working but not necessarily correct solution could be:

  interact f = do
  s <- getContents
  length s `seq` putStr (f s)

This one is probably better:

  interact f = do
  s <- getContents
  foldr seq () s `seq` putStr (f s)

And this is more fun ;) :

  interact f = do
  s <- getContents
  foldr seq (putStr (f s)) s

> Thanks, Christian

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Christian Maeder
I wrote:
But looking at the two actions of interact:

interact f = do
   s <- getContents
   putStr (f s)
>>
I would expect the first action to be finished before the second
Keith Wansbrough wrote:
Why?
Because the actions are written down in that order? Why not? Why should 
I expect pipelining? Occam's razor demands the simplest theory.

For the use of laziness, consider

let fib = 0 : 1 : zipWith (+) fib (tail fib) in fib

and think what would happen if "let" was strict.  Programming in 
Haskell can be much more convenient than in strict languages, and 
laziness is assumed in lots of little ways throughout idiomatic Haskell 
code (I'm thinking of the liberal use of "where" and "let" bindings, 
for example).
I know and appreciate these uses of laziness. There are plenty of 
examples where eager or lazy evaluation can bite you or save you. It's 
good to have both, and even better if you do not need to worry about it 
too often.

getContents behaves according to the specification in the standard, 
which is good enough for me.  So does putStr.
Allow me to have another opinion, if the consequence is interleaved in- 
and output (when I don't want it).

Can actually someone supply an implementation of something like interact 
that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
!$ s" was not enough!

HTH.
Thanks, Christian

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Olaf Chitil

Robert Ennals wrote:
> > No, optimistic evaluation does not work well with interact, because it
> > causes the input stream to be evaluated (and therefore demanded) earlier
> > than you would expect.  This is the problem: interact exposes more than
> > just non-strictness, it exposes laziness.
> >
> > In Robert Ennals' implementation of optimistic evaluation he has to fall
> > back to lazy evaluation for lazy I/O, precisely because of this problem.
> 
> Or to put it another way.
> 
> Optimistic Evaluation works fine with "interact". You can write programs that
> use interact, evaluate them optimistically, and they will behave exactly as
> they always did.

Good to hear that ;-)

I still do not quite agree with Simon that 'interact' exposes anything
but non-strictness. Non-strictness means that

  map toUpper _|_ = _|_
  map toUpper ('a':_|_) = ('A':_|_)
  map toUpper ('a':'b':_|_) = ('A':'B':_|_)

and 'interact (map toUpper)' is a great way to experience this property.

However, you can also experience the property without 'interact',
evaluating expressions like

  take 2 (map toUpper ('a':'b':undefined))

I suppose Simon finds it annoying that optimistic evaluation has to deal
specially with 'interact' (or actually the primitive that really
implements it). I do not find that surprising. When you define an
evaluation strategy you have to define it for all language constructs,
including special primitives. If many of the special primitives don't
need special treatment, that is nice, but it cannot be expected in
general.

Olaf

-- 
OLAF CHITIL, 
 Dept. of Computer Science, The University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Imported instance declarations

2003-10-01 Thread Frieder Kalisch
Hello,

While trying to learn Hakell I came across a weird (to me) error message
concerning imported instance declarations.

This module

module XXX() where

import Control.Monad.Error()

instance Functor ((->)i) where
  fmap = (.)

gives this error message (compiling with ghc 5.0.4.2):

Duplicate instance declarations:
  XXX.hs:5: Functor ((->) i)
  : Functor ((->) r)

For me this error message is somewhat puzzling: Where is the second
instance declaration given? In this case it happens to be in
Control.Monad.Reader, but how can I find out without looking for it
in the CVS repository? The documentation for Control.Monad.Error does
not mention the imported modules.

I suppose, that the compiler knows in which module the instance 
declaration was given, because it needs to tell duplicate import paths 
from duplicate instance declarations. Why is it not given in this example?

Greetings

  Frieder Kalisch


-- 
Frieder Kalisch
[EMAIL PROTECTED]
+49-6221-549-432

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Robert Ennals

[snip]

> No, optimistic evaluation does not work well with interact, because it
> causes the input stream to be evaluated (and therefore demanded) earlier
> than you would expect.  This is the problem: interact exposes more than
> just non-strictness, it exposes laziness.
> 
> In Robert Ennals' implementation of optimistic evaluation he has to fall
> back to lazy evaluation for lazy I/O, precisely because of this problem.

Or to put it another way.

Optimistic Evaluation works fine with "interact". You can write programs that 
use interact, evaluate them optimistically, and they will behave exactly as 
they always did.

Optimistic Evaluation takes care to never speculatively evaluate anything that 
could have externally visible effects.



It is a guiding principle of Optimistic Evaluation that there should be no 
user-perceivable difference between optimistic evaluation and lazy evaluation.


-Rob

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: "interact" behaves oddly if used interactively

2003-10-01 Thread Simon Marlow
 
> Pardon? Haskell is a non-strict language. Using 'interact' is one of
> numerous situations where one takes advantage of non-strict semantics.
> (Keith just gave a different example.)
>
> Non-strict semantics does not prescribe the evaluation order, although
> usually lazy evaluation is used. I suppose you are talking about
> optimistic evaluation, which is a mixture of eager and lazy 
> evaluation.

Yes sorry, I meant optimistic evaluation.

> That is fine and should work well with 'interact', otherwise there is
> something wrong with optimistic evaluation.

No, optimistic evaluation does not work well with interact, because it
causes the input stream to be evaluated (and therefore demanded) earlier
than you would expect.  This is the problem: interact exposes more than
just non-strictness, it exposes laziness.

In Robert Ennals' implementation of optimistic evaluation he has to fall
back to lazy evaluation for lazy I/O, precisely because of this problem.

Cheers,
Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: "interact" behaves oddly if used interactively

2003-10-01 Thread Koen Claessen
Simon Marlow wrote:

 | For example, eager evaluation would be a completely
 | valid implementation strategy for Haskell if it were
 | not for lazy I/O.

I do not understand this remark.

As far as I know, in any valid implementation of Haskell,
the following expression:

  const 3 undefined

should always produce 3; any valid evaluation strategy for
Haskell should respect not trying to evaluate something like
undefined if it is not needed for the computation.

I see no difference between that and that any valid Haskell
implementation should avoid trying to read a character from
the input if it is not needed.

/Koen

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Olaf Chitil
Simon Marlow wrote:
> 
> Malcolm Wallace writes:
> > But the whole purpose of 'interact' is to use its argument as the
> > demanding function which drives lazy consumption of the input.  It is
> > *designed* to reveal the evaluation behaviour, by hoisting it into
> > the I/O monad.
> 
> This is why interact is bad, IMO: it forces you to think about the
> evaluation order.  The evaluation order for Haskell is not part of the
> language definition - it is normally up to the implementation to pick a
> strategy.
> 
> Except when you get to lazy I/O.  The commonly accepted meaning for the
> lazy I/O operations forces the implementation to adopt a lazy evaluation
> strategy for values which require lazy I/O.  For example, eager
> evaluation would be a completely valid implementation strategy for
> Haskell if it were not for lazy I/O.

Pardon? Haskell is a non-strict language. Using 'interact' is one of
numerous situations where one takes advantage of non-strict semantics.
(Keith just gave a different example.)

Non-strict semantics does not prescribe the evaluation order, although
usually lazy evaluation is used. I suppose you are talking about
optimistic evaluation, which is a mixture of eager and lazy evaluation.
That is fine and should work well with 'interact', otherwise there is
something wrong with optimistic evaluation. Certainly pure eager
evaluation is not a valid evaluation strategy for Haskell.

Olaf 

-- 
OLAF CHITIL, 
 Dept. of Computer Science, The University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Keith Wansbrough
> But looking at the two actions of interact:
> 
> interact f = do
> s <- getContents
> putStr (f s)

(The Haskell report has two more actions, btw, setting nobuffering here)

> I would expect the first action to be finished before the second, (and I 

Why?

The magic here, in any case, is in getContents, which returns a list 
that is *lazily evaluated as needed* (Haskell report, page 98 (sec 
7.1)).  hGetContents does the same for an arbitrary handle.  This 
allows you to replicate the behaviour of Unix cat, ncat, grep etc, 
without having to code it explicitly.

For the use of laziness, consider

let fib = 0 : 1 : zipWith (+) fib (tail fib) in fib

and think what would happen if "let" was strict.  Programming in 
Haskell can be much more convenient than in strict languages, and 
laziness is assumed in lots of little ways throughout idiomatic Haskell 
code (I'm thinking of the liberal use of "where" and "let" bindings, 
for example).

> would not call it "interact" anymore after this discussion).

> Therefore, the "primitives" (getContents, putStr) behave "incorrect" to 
> my taste, (although the actual behaviour may be more desirable for 
> special other purposes.)

getContents behaves according to the specification in the standard, 
which is good enough for me.  So does putStr.

> 
> Christian

HTH.

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: "interact" behaves oddly if used interactively

2003-10-01 Thread Simon Marlow
Malcolm Wallace writes:
> But the whole purpose of 'interact' is to use its argument as the
> demanding function which drives lazy consumption of the input.  It is
> *designed* to reveal the evaluation behaviour, by hoisting it into
> the I/O monad.

This is why interact is bad, IMO: it forces you to think about the
evaluation order.  The evaluation order for Haskell is not part of the
language definition - it is normally up to the implementation to pick a
strategy.

Except when you get to lazy I/O.  The commonly accepted meaning for the
lazy I/O operations forces the implementation to adopt a lazy evaluation
strategy for values which require lazy I/O.  For example, eager
evaluation would be a completely valid implementation strategy for
Haskell if it were not for lazy I/O.

This has been swept under the carpet for far too long!

Cheers,
Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Jerzy Karczmarczuk
Christian Maeder wrote:
Colin Runciman wrote:

Let not the eager imperative tail wag the lazy functional dog!


Ideally functional programs should be independent of evaluation strategy 
and I assume that this is the case for about 90% of all Haskell 
programs. This leaves maybe the head or only the nose for laziness of 
the "functional dog".


"Ideally"?

You just proved that you never *needed* laziness in your life.
There is a full-fledged category of functional programs which wouldn't work
without laziness. Saying that it is 10, or 0.1% has simply no sense.
Colin demonstrated one such category.
I need laziness to implement co-recursive data structures for scientific
applications.
(If you wish, have another Great Truth:

   "Ideally any programs should be independent of the language used for
coding them..."
Now, try to convince the world.

)



Jerzy Karczmarczuk

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Christian Maeder
Colin Runciman wrote:
Let not the eager imperative tail wag the lazy functional dog!
Ideally functional programs should be independent of evaluation strategy 
 and I assume that this is the case for about 90% of all Haskell 
programs. This leaves maybe the head or only the nose for laziness of 
the "functional dog".

But looking at the two actions of interact:

interact f = do
   s <- getContents
   putStr (f s)
I would expect the first action to be finished before the second, (and I 
would not call it "interact" anymore after this discussion).

Therefore, the "primitives" (getContents, putStr) behave "incorrect" to 
my taste, (although the actual behaviour may be more desirable for 
special other purposes.)

Christian

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Colin Runciman
Christian Maeder wrote:

Malcolm Wallace wrote:
[...]
Surely the name suggests that "interactive" behaviour is required, i.e.
exactly some interleaving of input and output.  The chunk-size of the
interleaving should depend only on the strictness of the argument to
"interact". 


I'm not happy that interleaving depends on the strictness. Lazy or 
strict evaluation should only change the behaviour of overall 
termination (lazy evaluation should terminate more often). I'ld rather 
implement interleaving (or "interactive" behaviour) explicitely by:

interact f = do
  s <- getLine
  putStrLn (f s)
  interact f
(assuming line buffering) (Terminating with "ctrl-c")

Surely also something is needed for endless character resources as
Tom pointed out.
Christian
In a lazy language, evaluation of arguments and results is interleaved.
This coroutine-like behaviour is an important and pleasing
characteristic, not a mistake to be avoided.
Lazy evaluation of String -> String functions with the argument attached
to an input device  (eg. keyboard) and the result attached to an output
device (eg. screen) is therefore a conceptually lean and natural way
to express sinple interactive programs in a lazy functional language.  

Historically, the wish to preserve the option of looking at interaction
this way, if only for pedagogical reasons, was the reason for keeping
the interact function in Haskell even after the monadic revolution.
If line-buffering is needed, it is easily programmed in Haskell as
a (lazily evaluated!) function lineBuffered :: String -> String.
If f :: String -> String is the core function of the program one can
define main = interact (f . lineBuffered) and the fact that the
program relies on line-buffered input is clearly expressed in the
program itself.
Conversely, if line-buffering is built-in as part of interact, there
is no way to program it out when defining interact's argument.
Let not the eager imperative tail wag the lazy functional dog!

Colin R



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Olaf Chitil
Christian Maeder wrote:
> 
> Malcolm Wallace wrote:
> [...]
> > Surely the name suggests that "interactive" behaviour is required, i.e.
> > exactly some interleaving of input and output.  The chunk-size of the
> > interleaving should depend only on the strictness of the argument to
> > "interact".
> 
> I'm not happy that interleaving depends on the strictness. Lazy or
> strict evaluation should only change the behaviour of overall
> termination (lazy evaluation should terminate more often). 

I disagree with your point of view. Non-strictness is an essential
feature of Haskell that any Haskell programmer should learn about soon.
The use of an interleaving function interact helps to understand
non-strictness. Also it shows that Haskell doesn't need a set of
additinal primitives to deal with IO (the IO monad), but that
non-strictness can provide the basis for IO. You only need as single
primitive function, interact, that connects your non-strict IO function
to the external world. I do not claim that this IO model is the best for
programming in the large, but you can learn a lot from it.

> Surely also something is needed for endless character resources as
> Tom pointed out.

An "interactive" interact is fine for that.

Olaf

-- 
OLAF CHITIL, 
 Dept. of Computer Science, The University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Malcolm Wallace
Christian Maeder <[EMAIL PROTECTED]> writes:

> I'm not happy that interleaving depends on the strictness. Lazy or 
> strict evaluation should only change the behaviour of overall 
> termination (lazy evaluation should terminate more often).

But the whole purpose of 'interact' is to use its argument as the
demanding function which drives lazy consumption of the input.  It is
*designed* to reveal the evaluation behaviour, by hoisting it into
the I/O monad.

(AFAIK, 'interact' was explicitly designed for beginners, as an easy
way to turn a pure computation into one which will actually run,
before they learn about the I/O monad.  Anyone from the original
Haskell committee should feel free to correct me at this point,
but interact was never intended for "serious" users.)

> I'ld rather 
> implement interleaving (or "interactive" behaviour) explicitely by:
> 
> interact f = do
>s <- getLine
>putStrLn (f s)
>interact f

Your suggested implementation does not have anything like the same
semantics as the current 'interact'.  For instance, consider the
following program to number the lines of its input:

main = interact (unlines . zipWith lineno [0..] . lines)
  where lineno n s = shows n (" "++s)

Your version of interact behaves very unintuitively here!
Regards,
Malcolm
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Christian Maeder
Malcolm Wallace wrote:
[...]
Surely the name suggests that "interactive" behaviour is required, i.e.
exactly some interleaving of input and output.  The chunk-size of the
interleaving should depend only on the strictness of the argument to
"interact". 
I'm not happy that interleaving depends on the strictness. Lazy or 
strict evaluation should only change the behaviour of overall 
termination (lazy evaluation should terminate more often). I'ld rather 
implement interleaving (or "interactive" behaviour) explicitely by:

interact f = do
  s <- getLine
  putStrLn (f s)
  interact f
(assuming line buffering) (Terminating with "ctrl-c")

Surely also something is needed for endless character resources as
Tom pointed out.
Christian



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Marc A. Ziegert
> "main=interact id" basically echoes every line of my input, whereas
> "main=interact show" correctly waits for EOF before outputting something.

> What should a student think about "interact" in the Prelude? (It's ok 
> for pipes only, I guess.)


main = interact show
behaves similar to
main = interact (\x->seq (length x) x)


i do not know the exact implementation, but i think of it like ...


import System.IO(hGetContents,hIsEOF,hGetChar,stdin)
import System.IO.Unsafe (unsafePerformIO)

interact :: (String -> String) -> IO ()
interact f = do s <- hGetContents stdin
putStr $ f s

putStr = mapM_ putChar

hGetContents h = do eof <- hIsEOF h
if eof then return []
   else c <- hGetChar h
return (c : (unsafePerformIO $ hGetContents h))


... so there will be the same problems like with getChar, hGetChar, getLine, or 
hGetLine (buffering), and with hGetContents and unsafePerformIO (sequrence of IOs).


for beginners/students: think about such situations: (to me, it was the reason to 
learn IO monadic programming)
read the next char(s) from input before writing the previous char(s) to output.

f :: String -> String
f [] = []
f (c:[]) = (c:[])
f (c:s) = (c:f s)

equals to

f :: String -> String
f [] = []
f (c:[]) = (c:[])
f (prev:s@(next:_)) = (prev:f s)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Malcolm Wallace
Christian Maeder <[EMAIL PROTECTED]> writes:

> I guess "interact" does what it should, but I think it should be changed 
> to avoid interleaved in- and output.

Surely the name suggests that "interactive" behaviour is required, i.e.
exactly some interleaving of input and output.  The chunk-size of the
interleaving should depend only on the strictness of the argument to
"interact".  Unfortunately, the visible behaviour can also currently
depend on buffering and echoing of the input (and possibly also
buffering of the output), which I feel is a mistake.

Regards,
Malcolm
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Tomasz Zielonka
On Tue, Sep 30, 2003 at 03:52:50PM +0200, Christian Maeder wrote:
> Hi,
> 
> For GHC (6.0.1)
> 
> "main=interact id" basically echoes every line of my input, whereas
> "main=interact show" correctly waits for EOF before outputting something.

That's only because output to terminal is line buffered by default and
show converts all newlines to \n.

Try feeding it from /dev/urandom or similar endless character resource -
you'll see that it doesn't wait for EOF.

PS. The name 'interact' suggests interaction :)

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Christian Maeder
I wrote:
"main=interact id" basically echoes every line of my input, whereas
"main=interact show" correctly waits for EOF before 
outputting something.
The unix "cat" and "sort" behave in a similar way ("sort" obviuously has 
to wait for the last line.)

Still I would regard it to be more "pure" (or "abstract") if my input 
would always be mapped to visibly separate output.

Christian

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: type class problem

2003-10-01 Thread Martin Sulzmann

There's another possible fix which makes use of scoped variables.

instance (RT r1 t1, RT r2 t2, TPair t t1 t2) => RT (RPair r1 r2) t where
  rtId (RPair r1 r2) t = "RT (RPair " ++ rtId r1 t1 ++ " " ++ rtId r2 t2 ++")"
where (t1::t1,t2::t2) = prj t
  ^^
 scoped variables

Martin



 > 
 > Dean Herington wrote:
 > > Can someone explain why the following doesn't work?
 > 
 > > {-# OPTIONS -fglasgow-exts #-}
 > 
 > > class R r where
 > >   rId :: r -> String
 > 
 > > class (R r) => RT r t where
 > >   rtId :: r -> t -> String
 > 
 > > data RPair r1 r2 = RPair r1 r2
 > 
 > > instance (R r1, R r2) => R (RPair r1 r2) where
 > >   rId (RPair r1 r2) = "RPair " ++ rId r1 ++ " " ++ rId r2
 > 
 > > class TPair t t1 t2 where
 > >   prj :: t -> (t1,t2)
 > >   inj :: (t1,t2) -> t
 > 
 > > instance (RT r1 t1, RT r2 t2, TPair t t1 t2) => RT (RPair r1 r2) t where
 > >  rtId (RPair r1 r2) t = "RT (RPair " ++ rtId r1 t1 ++ " " ++ rtId r2 t2 ++")"
 > >where (t1,t2) = prj t
 > 
 > You need a functional dependency. For example:
 > 
 > class TPair t t1 t2 | t->t1 t2 where
 >   prj :: t -> (t1,t2)
 >   inj :: (t1,t2) -> t
 > 
 > with this definition, the typechecker is satisfied.
 > 
 > Without the dependency, the compiler assumes that there may be several
 > instances:
 >  TPair t t1 t2
 > and
 >  TPair t t1' t2'
 > 
 > You claimed that RT r1 t1 and RT r2 t2 holds. But you didn't promise
 > that RT r1 t1' and RT r2 t2' will also hold. In other words,
 >  (RT r1 t1, RT r2 t2, TPair t t1 t2)
 > reads as
 >  (exists t1 t2. RT r1 t1, RT r2 t2, TPair t t1 t2)
 > rather than
 >  (forall t1 t2. RT r1 t1, RT r2 t2, TPair t t1 t2)
 > (which you need to guarantee that the definition of (t1,t2) = prj t
 > can be typechecked). Notice that forall is _inside_ of parentheses,
 > on the assumption side (the negative side). 
 > 
 > ___
 > Haskell mailing list
 > [EMAIL PROTECTED]
 > http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell