[ ghc-Bugs-815511 ] Floating pt. arithmetic bugs / inexplicable inaccuracy

2003-10-01 Thread SourceForge.net
Bugs item #815511, was opened at 2003-09-30 23:48 Message generated for change (Comment added) made by simonmar You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=815511group_id=8032 Category: None Group: None Status: Open Resolution: None Priority: 5

[ ghc-Bugs-815511 ] Floating pt. arithmetic bugs / inexplicable inaccuracy

2003-10-01 Thread SourceForge.net
Bugs item #815511, was opened at 2003-09-30 16:48 Message generated for change (Comment added) made by nobody You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=815511group_id=8032 Category: None Group: None Status: Open Resolution: None Priority: 5 Submitted

[ ghc-Bugs-792761 ] rts_getBool: not a Bool

2003-10-01 Thread SourceForge.net
Bugs item #792761, was opened at 2003-08-21 20:46 Message generated for change (Comment added) made by simonmar You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=792761group_id=8032 Category: None Group: None Status: Closed Resolution: None Priority: 5

[ ghc-Bugs-815511 ] Floating pt. arithmetic bugs / inexplicable inaccuracy

2003-10-01 Thread SourceForge.net
Bugs item #815511, was opened at 2003-09-30 23:48 Message generated for change (Settings changed) made by simonmar You can respond by visiting: https://sourceforge.net/tracker/?func=detailatid=108032aid=815511group_id=8032 Category: None Group: None Status: Closed Resolution: None Priority: 5

peekCString stack overflow

2003-10-01 Thread George Russell
The following program gives me a stack overflow for a file big.tex 15 bytes long. -- Cut here -- module Main where import Foreign.C.String import Foreign.Ptr import qualified GHC.IO main = do (ptr,len) - GHC.IO.slurpFile big.tex peekCStringLen (castPtr ptr,len) return ()

RE: peekCString stack overflow

2003-10-01 Thread Simon Marlow
The following program gives me a stack overflow for a file big.tex 15 bytes long. -- Cut here -- module Main where import Foreign.C.String import Foreign.Ptr import qualified GHC.IO main = do (ptr,len) - GHC.IO.slurpFile big.tex peekCStringLen (castPtr

Re: peekCString stack overflow

2003-10-01 Thread Alastair Reid
Yes, I've run into this before. In fact this is one of those tricky problems where you can't quite get tail-recursion where you want it: (pseudo-ish code follows) peekCString ptr = do x - peek ptr if x == '\0' then return [] else do xs - peekCString (ptr + 1)

Re: peekCString stack overflow

2003-10-01 Thread Ross Paterson
On Wed, Oct 01, 2003 at 05:34:47PM +0100, Alastair Reid wrote: Yes, I've run into this before. In fact this is one of those tricky problems where you can't quite get tail-recursion where you want it: (pseudo-ish code follows) peekCString ptr = do x - peek ptr if x ==

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

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)

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

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

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

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

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

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

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

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

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

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

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

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

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

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'

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

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

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?

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

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.

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

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

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 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

RE: swap leak problem

2003-10-01 Thread Simon Marlow
Oh yes, one more datum. If I run hs_perform_gc before each and every mallocForeignPtrBytes and reallocBytes, the leak goes much more slowly, and the code gets much further in the job before getting killed. But it still leaks, and still gets killed. It could potentially be a memory

Re: Haskell-beginners problem with memory consuption

2003-10-01 Thread Wolfgang Jeltsch
Am Mittwoch, 1. Oktober 2003, 15:18 schrieb Petter Egesund: [...] The problem is of course that the string is copied each time I do a substitute, and I wonder if a more experienced haskeller has a better solution to my problem. It doesn't have to be a problem that the string is copied each

SV: Haskell-beginners problem with memory consuption

2003-10-01 Thread Petter Egesund
Hi thanks for answering; I should have been more precise, my function works like this: fun :: String - String look for pat1 in string - if found subst with sub1 look for pat2 in string - if found subst with sub2 look for pat3 in string - if found subst with sub3

RE: interact behaves oddly if used interactively

2003-10-01 Thread Simon Marlow
[ taking this one to haskell-café... ] 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

Another beginner's memory consumption problem...

2003-10-01 Thread Bayley, Alistair
I'm trying the add-a-gram challenge from here: http://www.itasoftware.com/careers/programmers-archive.php ... and I'm also experiencing runaway memory consumption. If I load the supplied list of words (a 1.6M file) and search for shorter strings, things are OK. Memory consumption increases

Re: interact behaves oddly if used interactively

2003-10-01 Thread Olaf Chitil
Simon Marlow wrote: Certainly you can observe non-strictness, that's not the point. The point is that you can also observe more than just non-strictness using interact, and I don't think that is desirable. For example: interact (\xs - let z = length xs in Hello World\n) Now, Haskell

Re: interact behaves oddly if used interactively

2003-10-01 Thread Olaf Chitil
Robert Ennals wrote: It is wrong for all the same reasons that unsafePerformIO is wrong, except that it is worse than that because unsafePerformIO has unsafe in the title, and people are discouraged from using it without due care. By contrast, interact and getContents are presented as being

RE: interact behaves oddly if used interactively

2003-10-01 Thread Simon Marlow
Yes, the presence of lazy IO makes optimistic evaluation more complicated, but I do not see that it compromises the purity of the language in anyway (whatever purity is ;-). So, we're agreed that the presence of lazy evaluation makes implementing optimistic evaluation (and other evaluation