Strictness

1993-10-27 Thread ian
Following recent discussions about strictness annotations, and the reservations people had about introducing them into standard Haskell, I thought I would mention that there is another way of thinking about them that might be helpful. You can think of a type !t as meaning `t without _|_

Re: Strictness!

2002-03-14 Thread Jay Cox
On Thu, 14 Mar 2002, Brian Huffman wrote: > In Haskell you can produce the desired behavior by using pattern guards. > Since the pattern guards always get evaluated before the result does, they > can be used to make things more strict. Here is the foldl example: > > strict x = seq x True > > fold

Re: Strictness

2002-03-15 Thread Ronny Wichers Schreur
matt hellige writes (to the haskell mailing list): >[..] consider: >sum 0 x = x >sum x y = x + y > >if the first argument is 0, we don't need to inspect the second >argument at all. But sum returns its second argument, so it's still strict in that argument. Cheers, Ronny Wichers Schr

Re: Strictness

2002-03-15 Thread Jay Cox
Alright. I know the haskell community probably gets tired of my long winded posts. I This post probably shouldn't even be on [EMAIL PROTECTED] (more like on haskell-cafe). I also realize that these posts may not mean much to you; many of you may have figured out most of this strictness bus

Re: Strictness

2002-03-16 Thread Wolfgang Jeltsch
On Saturday, March 16, 2002, 03:16 CET Jay Cox wrote: > [...] > I think I may eventually attempt to write a haskell lazyness/strictness FAQ. Great! I'm very interested in it. > [...] Wolfgang ___ Haskell mailing list [EMAIL P

Re: Strictness!

2002-03-18 Thread Carl R. Witty
Jay Cox <[EMAIL PROTECTED]> writes: > On Thu, 14 Mar 2002, Brian Huffman wrote: > > > In Haskell you can produce the desired behavior by using pattern guards. > > Since the pattern guards always get evaluated before the result does, they > > can be used to make things more strict. Here is the fo

strictness question

2001-03-02 Thread S. Doaitse Swierstra
I ran into a difference between GHC and Hugs. The following code: f (P p) ~(P q) = P (\ k -> \inp -> let (((pv, (qv, r)), m), st) = p (q k) inp in (((pv qv , r ), m), st)) runs fine with Hugs but blows up with GHC, whereas: f (P p) ~(P q) = P (\ k

Strictness annotations

1993-10-09 Thread Warren Burton
I like the idea of having some way to force the evaluation of things in a functional language. For example, it seems like a good idea to be able to force both components of a complex number to be evaluated always. However, I see one problem with strictness annotations in a data declaration

Re: Strictness

1993-10-28 Thread hudak-paul
(This is a message on strictness, etc. I was too busy to reply earlier when the discussion first began). Like Ian, I would like to suggest that we lift functions in Haskell. Originally there was a good reason not to: there was no need (and indeed no way) to distinguish _|_ from \x->_|_.

Re: Strictness

1993-10-29 Thread wadler
Paul writes, What are the disadvantages of having a lifted function space? I think the main one is that we lose unrestricted eta conversion. But maybe that's not such a big deal either. We keep claiming that functional languages are good because they satisfy lots of la

Re: Strictness

1993-10-29 Thread wadler
I've separated this from my previous note, because it's about the precise question of strictness annotations rather than the more general question of laws. I would rather tell someone that to define a new type exactly isomorphic to an old type they need to write new

Re: Strictness

1993-10-29 Thread Lennart Augustsson
Phil writes: > In the absence of convincing answers, I'd rather have as many laws > as possible, hence my preference for unlifted tuples and products. Here's another law that I find useful: If we write f p = p where p is some pattern&expression then I expect f to be the identity func

Re: Strictness

1993-10-29 Thread ian
Paul and Phil write, | What are the disadvantages of having a lifted function space? | | I think the main one is that we lose unrestricted eta | conversion. But maybe that's not such a big deal either. | | We keep claiming that functional languages are good because they | sa

Re: Strictness

1993-10-29 Thread wadler
If Lennart was asking, `Shall we make laws a paramount design feature of Haskell, and therefore go for unlifted tuples, unlifted functions, and no n+k or literal patterns', my answer would be `let's go for it'. But I suspect what Lennart is really asking is `Shall we ignore laws, have lifted tup

Re: Strictness

1993-10-29 Thread hudak-paul
plus constants. Maybe this is even more reason to put strictness into the type system! :-) Similarly, given an equation: f (Foo x y) = y If Foo is strict in its first component then I can't use this equation at will; I need to qualify it: f (Foo x y) = yif x /= _|_ (And ag

Re: Strictness

1993-10-29 Thread wadler
Paul writes, I think it's important to realize that laws aren't being entirely lost -- they're just being weakened a (wee) bit, in the form of carrying an extra constraint. For example, eta conversion: \x -> f x = f must simply be modified slightly: \x -

Re: Strictness

1993-10-29 Thread hudak-paul
ain I point out that despite our original intents, we still need to reason about _|_'s -- in pattern-matching, for example -- and "strictness bugs" have become infamous (:-)! -Paul

Re: Strictness

1993-10-31 Thread Warren Burton
Strictness annotations do not completely remove the need for unlifted products. (However, on balance I am inclined to stay with lifted products only, rather than add a new language feature.) In a lifted product, bottom /= (bottom, bottom). That is, a new bottom is added onto the produce

Re: Strictness

1993-10-31 Thread Warren Burton
Strictness annotations are not annotations, since they change the meaning of a program. Let's use the term strictness indicators. As I mentioned in an earlier message to this mail group, with > f (Pair a b) = b the value of (f (Pair x 5)) may not be 5, when Pair involves st

Re: Strictness

1993-11-01 Thread Joe Fasel
he type, and also, bottom and (\x -> bottom) could probably be trivially distinguished by an isFunction type predicate.) Your implementation may well have different representations corresponding to bottom and (\x -> bottom), but that's a far cry from saying that they shouldn't abstrac

Re: Strictness

1993-11-01 Thread arvind
Theoretical arguments regarding the distinction between lifted vs unlifted tuples (i.e., any type declaration with single disjunct) are too esoteric for my taste. However, there are some practical reasons to choose one over the other. In the Id implementation, no distinction is made between li

Re: Strictness

1993-11-02 Thread Lennart Augustsson
> To correctly evaluate seq (x, y) 5 it would be necessary to concurrently > evaluate x and y, since (x, y) is bottom if and only if both x and y are > bottom. (I enjoy finding a flaw in Miranda because there are so few to > be found!) Another flaw: There is a seq hidden in foldl. -

Re: Strictness

1993-10-31 Thread Warren Burton
Paul Hudak notes: |Similarly, given an equation: | | f (Foo x y) = y | | |If Foo is strict in its first component then I can't use this equation |at will; I need to qualify it: | | f (Foo x y) = yif x /= _|_ | | |(And again, the first equ

Re: Strictness

1993-10-29 Thread hudak-paul
I would rather tell someone that to define a new type exactly isomorphic to an old type they need to write newtype Type = Constructor typeexp then tell them that they need to write data Type = Constructor !typeexp The latter smacks too much of magic. This is clearly a m

[Haskell] Strictness question

2005-06-07 Thread Gary Morris
Hello everyone, I've been playing with implementing the Kocher attacks on RSA in Haskell. For the simplest version, I decided to implement the exponentiation in the same module. However, my initial tests suggest that the times don't have any correlation with the operations being performed. I'm

stupid strictness question

2002-12-04 Thread Hal Daume III
ing on K is not affected by strictness flags. so. we define: > data L = L Int deriving Show > data S = S !Int deriving Show and, as expected, we get: *Strict> L undefined L *** Exception: Prelude.undefined *Strict> L $! undefined *** Exception: Prelude.undefined *Strict>

Guidance on strictness

1999-06-05 Thread Juan Jose Garcia Ripoll
Hi, can anybody point me to tutorials, papers, etc, on how to properly annotate strictness in Haskell code? I am concerned with the following stupid piece of code that eats a lot of memory and takes an incredible amount of time to produce some output. I hope somebody will help me in finding what

strictness annotations & efficiency

1999-07-20 Thread Fergus Henderson
On 19-Jul-1999, Jan Brosius <[EMAIL PROTECTED]> wrote: > will Haskell compiled programs be faster by using more strictness > annotations; Strictness annotations on functions don't help much, since the compilers generally do a fine job of inferring strictness of functions. But th

Re: strictness question

2001-03-02 Thread Marcin 'Qrczak' Kowalczyk
Thu, 1 Mar 2001 12:25:33 +0100, S. Doaitse Swierstra <[EMAIL PROTECTED]> pisze: > From the Haskell manual I understand that pattern matching in "let"'s > should be done lazily, so the addition of a collection of ~'s should > not make a difference. Toplevel ~ in let doesn't change anything. But

RE: strictness question

2001-03-02 Thread S. Doaitse Swierstra
t;Adding more twiddles means less eager matching. I don't know whether >Hugs implements this. > >Simon > >| -Original Message- >| From: S. Doaitse Swierstra [mailto:[EMAIL PROTECTED]] >| Sent: 01 March 2001 11:26 >| To: [EMAIL PROTECTED] >| Subject: strictn

Re: strictness question

2001-03-02 Thread Dylan Thurston
On Fri, Mar 02, 2001 at 06:58:16PM +, Marcin 'Qrczak' Kowalczyk wrote: > Toplevel ~ in let doesn't change anything. But nested ~'s do make > a difference. When a variable of a pattern is evaluated, the whole > pattern is matched. When you protect a subpattern by ~ deferring its > matching and

RE: strictness question

2001-03-02 Thread Simon Peyton-Jones
etc Adding more twiddles means less eager matching. I don't know whether Hugs implements this. Simon | -Original Message- | From: S. Doaitse Swierstra [mailto:[EMAIL PROTECTED]] | Sent: 01 March 2001 11:26 | To: [EMAIL PROTECTED] | Subject: strictness question | | | I ran into a differ

Strictness in Haskell

1992-04-08 Thread Cornel Klein
Hi ! Can anyone tell me whether it's possible to force Haskell to evaluate an expression strict ? Consider the following Haskell program: --- module Mergesort where data Sequ a = Empty | Cons (a,Sequ a) merge

Strictness in Haskell

1992-04-08 Thread john peterson
As others have mentioned, Haskell does not provide a direct means for strict evaluation. While the class system can be used, the trick of f x = x | x == x is not guaranteed to work since == methods defined by the user may not have the desired strictness property. I could always put instance

Strictness in Haskell

1992-04-08 Thread smk
I like John's idea with a class Strict, but I think there should also be a second class Eval for computing whnf's: class Strict a where strict :: a -> Bool class Eval a where eval :: a -> Bool Example: for Complex we get: instance Strict a => Strict (

ADTs and strictness

1993-10-05 Thread Simon L Peyton Jones
(This message assumes we head for the strictness-annotation-on-constructor-arg solution. I'll respond to Phil's comments in my next msg.) The problem with polymorphic strictness ~~~ John asks what the problem is with strict constructor args. As L

ADTs and strictness

1993-10-05 Thread Sergio Antoy
I have been following this discussion with interest and I'd like some clarification. Wadler writes: > But just because they call it `lazy' doesn't mean that it really is > the essence of laziness. What is really been called `lazy' and how is the `essence of laziness' defined? Also, forgive my

More on strictness

1993-11-01 Thread Joe Fasel
I wrote: |Thus, it would indeed be reasonable for the type of seq to determine |that f x `seq` y is all right, whereas f `seq` y is not permissible. |Similarly, I think it would be consistent to have unlifted products, |but not give them data instances, so that (x,y) `seq` z is not allowed, |

strictness of List.transpose

1998-03-31 Thread Jonas Holmerin
The other day, I tried to transpose an infinite list of finite list: Simplified example: transpose (repeat [1..5]) This won't terminate, since transpose is defined as transpose :: [[a]] -> [[a]] transpose = foldr (\xs xss -> zipWith (:)

Re: [Haskell] Strictness question

2005-06-07 Thread Ben Lippmeier
Gary Morris wrote: ioexptmod :: Integer -> Integer -> Integer -> Int -> IO Integer ioexptmod base expt n keySize = return $! exptmod base expt n keySize My hope was that the use of $! would force it to compute the exponentiation while I was timing -- and the average times are around 30K cl

Re: [Haskell] Strictness question

2005-06-07 Thread Marcin 'Qrczak' Kowalczyk
Ben Lippmeier <[EMAIL PROTECTED]> writes: > To gloss over details: it'll reduce x far enough so it knows that it's > an Integer, but it won't nessesarally compute that integers value. No, Integers don't contain any lazy components. It statically knows that it's an integer. -- __("< M

Papers on strictness annotations

2002-06-25 Thread Robert Ennals
I know this is slightly off topic but... Does anyone know if there are any papers published anywhere on strictness annotations? It seems that it would be nice to be able to cite a paper on the concept, but, as far as I can tell, no such paper exists. -Rob

Papers on strictness annotations

2002-06-25 Thread Kevin Glynn
Ennals writes: > > I know this is slightly off topic but... > > > Does anyone know if there are any papers published anywhere on strictness > annotations? > > > It seems that it would be nice to be able to cite a paper on the concept, but, > as far as I

RE: stupid strictness question

2002-12-05 Thread Simon Marlow
ug. You may have seen this message while loading the source containing the strict constructor definition: WARNING: ignoring polymorphic case in interpreted mode. Possibly due to strict polymorphic/functional constructor args. Your program may leak space unexpectedly. which means that GHCi

Re: Guidance on strictness

1999-06-06 Thread Hans Aberg
At 14:29 +0200 1999/06/05, Juan Jose Garcia Ripoll wrote: >can anybody point me to tutorials, papers, etc, on how to properly >annotate strictness in Haskell code? I am concerned with the following >stupid piece of code that eats a lot of memory and takes an incredible >amount of tim

Re: Guidance on strictness

1999-06-07 Thread Jerzy Karczmarczuk
Hans Aberg tries to help me/JJGR : > At 10:40 +0100 1999/06/07, Jerzy Karczmarczuk wrote: > >When I tried (Hugs, +h4M, interactively, just show, no print) > >with 1, it bombs on control stack overflow. > > Is this a Windows version? The thing is that on primitive OS's, a parameter > stack ch

Re: Guidance on strictness

1999-06-07 Thread Hans Aberg
At 10:40 +0100 1999/06/07, Jerzy Karczmarczuk wrote: >When I tried (Hugs, +h4M, interactively, just show, no print) >with 1, it bombs on control stack overflow. Is this a Windows version? The thing is that on primitive OS's, a parameter stack check must often be implemented by hand in order t

Re: Guidance on strictness

1999-06-07 Thread Fernando Rubio
8BIT Juan Jose Garcia Ripoll wrote: > Hi, > > can anybody point me to tutorials, papers, etc, on how to properly > annotate strictness in Haskell code? I am concerned with the following > stupid piece of code that eats a lot of memory and takes an incredible > amount of time to

Re: Guidance on strictness

1999-06-07 Thread Joe English
Juan Jose Garcia Ripoll <[EMAIL PROTECTED]> wrote: > can anybody point me to tutorials, papers, etc, on how to properly > annotate strictness in Haskell code? I am concerned with the following > stupid piece of code that eats a lot of memory and takes an incredible > amount

Re: Guidance on strictness

1999-06-07 Thread Jerzy Karczmarczuk
is your *real* problem, your example is of course artificial. Anyway, if you ask about strictness annotations... I must say that until today I managed to gain a little time to have some extra beers thanks to the laziness rather than to strictness. Then of course foldl is a little delicate... Hans w

seq / strictness and laziness

2001-11-12 Thread Amanda Clare
I have some code which is being unnecessarily lazy (and occupying too much heap space). The code should read and process several files one by one. What's happening is that all files get read in but the processing is delayed by laziness, and the files are being retained. It looks something like th

Re: Strictness in Haskell

1992-04-08 Thread laufer
Cornel, > data Sequ a = Empty > | Cons (a,Sequ a) wieso verwendest Du hier nicht einfach [a]? > If the typevariable "a" would be restricted to range over the typeclass Eq, > the dirty trick of adding the guard > > n==n > > to the definition of mergesort could be used

Re: Strictness in Haskell

1992-04-08 Thread Kevin Hammond
> Hi ! > > Can anyone tell me whether it's possible to force Haskell to evaluate an > expression strict ? Yes, in general it's not possible. That is, I can't write a function evaluate :: a -> a which will force its argument to WHNF. I can, as you've noted, write a function: e

Re: Strictness in Haskell

1992-04-08 Thread laufer
My apologies for the previous message, which was intended to go to Cornel Klein only. -Konstantin

Re: Strictness in Haskell

1992-04-08 Thread Lennart Augustsson
> Yes, in general it's not possible. That is, I can't write a function > > evaluate :: a -> a > > which will force its argument to WHNF. I don't think you mean what you are actually saying, it's perfectly possible write evaluate :-) evaluate x = x This function will evaluate its a

Re: ADTs and strictness

1993-10-05 Thread Gerald Ostheimer
> So, as Lennart says, if we allow constructors to be strict in functions > then we have to change the semantics to distinguish _|_ from (\x -> _|_). > I, for one, am deeply reluctant to do so; I certainly have no good handle on > the consequences of doing so. Does anyone else? I thought this i

Re: ADTs and strictness

1993-10-05 Thread Lennart Augustsson
> I thought this inequality was one of the distinguishing characteristics of > lazy functional programming relative to the standard lambda-calculus. To > quote from Abramsky's contribution to "Research Topics in Functional > Programming", Addison-Wesley 1990: > >Let O == (\x.xx)(\x.xx) be t

Re: ADTs and strictness

1993-10-05 Thread wadler
Gerald Ostheimer notes that in Abramsky and Ong's lazy lambda calculus that (\x -> bottom) differs from bottom. That's correct. But just because they call it `lazy' doesn't mean that it really is the essence of laziness. I prefer to use the more neutral name `lifted lambda calculus' for their

Re: ADTs and strictness

1993-10-06 Thread John Launchbury
>But just because they call it `lazy' doesn't mean that it really is >the essence of laziness. I prefer to use the more neutral name `lifted >lambda calculus' for their calculus. I disagree. In the simplest case (just lambdas, variables and applications, i.e. no explicit constructors), it is *

Strictness and Unlifted Products

1993-11-09 Thread Warren Burton
here is more than one possible constructor for the type. Another solution, which generalizes an earlier proposal of mine for strictness annotations, is as follows. We allow lifted, unlifted and smash products. (In a smash product, if any component of a product is _|_ then the entire product

Re: strictness of List.transpose

1998-04-01 Thread Koen Claessen
Jeffrey R. Lewis wrote: | Hmm... indeed. I wonder if there's any reason why zipWith can't just be fully lazy | so that we don't need to twiddle with transpose. I.e., define it as: | | zipWith :: (a->b->c) -> [a]->[b]->[c] | zipWith z ~(a:as) ~(b:bs) = z a b : zi

Re: strictness of List.transpose

1998-03-31 Thread Jeffrey R. Lewis
Jonas Holmerin wrote: > The other day, I tried to transpose an infinite list of finite list: > Simplified example: > > transpose (repeat [1..5]) > > This won't terminate, since transpose is defined as > > transpose :: [[a]] -> [[a]] > transpose = foldr >

[Haskell] standard monads and strictness

2005-05-30 Thread Wolfgang Jeltsch
Hello, I looked at the implementation of Writer, WriterT, State, StateT, RWS and RWST. They all use tuples to knit the result with the written value and/or state. Now, there seems to be an inconsistency between the transformer and non-transformer variants concerning strictness. The non

Re: seq / strictness and laziness

2001-11-19 Thread Phil Trinder
Both parallel and sequential computation must be carefully controlled to produce good parallel and distributed Haskell programs. Several languages including Glasgow parallel Haskell and Eden use *evaluation strategies*: overloaded polymorphic functions to describe the amount of evaluation. >

Re: Papers on strictness annotations

2002-06-25 Thread Josef Svenningsson
Robert, Strictness annotations were proposed for Haskell in the paper "Implementing Haskell Overloading" by Lennart Augustsson. http://citeseer.nj.nec.com/augustsson93implementing.html It only has a small section on strictness annotations but this is as close as I can get to yo

Re: Papers on strictness annotations

2002-06-25 Thread Robert Ennals
> Robert, > > Strictness annotations were proposed for Haskell in the paper > "Implementing Haskell Overloading" by Lennart Augustsson. > > http://citeseer.nj.nec.com/augustsson93implementing.html > > It only has a small section on strictness annotations but

Re: Papers on strictness annotations

2002-06-25 Thread Salvador Lucas Alba
Robert Ennals wrote: > Although it proposes them for Haskell, it says itself that they were already > present in Clean Section 8.3 (6 pages) of Plasmeijer and van Eekelen's book Functional Programming and Parallel Graph Rewriting Addison-Wesley is devoted to (Clean-like)

Re: Papers on strictness annotations

2002-06-26 Thread Robert Ennals
> And in the olden days (Before Haskell) there was: > > Kewley and Glynn1989 > J.M. Kewley and K. Glynn. > Evaluation Annotations for Hope+. > In Glasgow Workshop on Functional Programming, Workshops in Computing, > pages 329-337, Fraserburgh, Scotland, 1989. Springer-Verlag. Now r

Re: Strictness of library implementations

2001-11-12 Thread Malcolm Wallace
> Ratio defines > data (Integral a) => Ratio a = !a :% !a > which GHC seems to implement as specified, but nhc and hugs seem to use > data (Integral a) => Ratio a = a :% a > Does this not have different strictness properties? It does. In nhc98's case, t

Re: seq / strictness and laziness

2001-11-12 Thread Dean Herington
`seq` forces evaluation of only the top-level construct in its first argument. (($!) similarly for its second argument.) I would guess your "newcounts" are structured (probably a tuple or list), in which case you are not forcing evaluation deeply enough. See http://haskell.org/pipermail/haskell

Re: seq / strictness and laziness

2001-11-12 Thread Amanda Clare
Dean Herington wrote: > > `seq` forces evaluation of only the top-level construct in its first > argument. (($!) similarly for its second argument.) I would guess your > "newcounts" are structured (probably a tuple or list), in which case you are > not forcing evaluation deeply enough. See > h

Re: seq / strictness and laziness

2001-11-12 Thread Olaf Chitil
Amanda Clare wrote: > > Dean Herington wrote: > > > > `seq` forces evaluation of only the top-level construct in its first > > argument. (($!) similarly for its second argument.) I would guess your > > "newcounts" are structured (probably a tuple or list), in which case you are > > not forcing

Re: seq / strictness and laziness

2001-11-12 Thread Hal Daume
Dean Herington wrote: > > `seq` forces evaluation of only the top-level construct in its first > argument. (($!) similarly for its second argument.) I would guess your > "newcounts" are structured (probably a tuple or list), in which case you are > not forcing evaluation deeply enough. See > ht

Re: seq / strictness and laziness

2001-11-12 Thread John Meacham
yeah, I doublevote for deepSeq being part of the libraries or a 'blessed' extension. I would like to do things like deepSeq the abstract tree of a compiled language then force a GC, thus making sure that the original file text gets all cleaned up properly. deepSeq would be a much nicer way of deal

Re: Lifted products (strictness annotations

1993-10-06 Thread Alan Baljeu
gt; (because of previous discussion about the difficulty with strictness in function > types), it does make perfect sense to say > > newtype New a b = MakeNew (a->b) > > In short, using a strictness "annotation" (not really an annotation anyway, > since it chang

Re: Strictness and Unlifted Products

1993-11-10 Thread wadler
In all of this, I neglected to mention *why* I think unlifted tuples are a good idea. I've given various reasons, but not the real one. The real one is: Embarassment. I wrote an implementation of linear logic in Haskell. It took a while before I discovered why my implementation got into a loo

[Haskell] strictness of putChar: report incomplete?

2005-10-04 Thread John Meacham
The report does not seem to specify whether putChar _|_ is _|_ or not. (although it might be implied somewhere I didn't see) I orginally noticed this when jhc treated it as so and I considered this a bug since the argument should not be evaluated until the action is actually executed. however,

Strictness (was: Is this tail recursive?)

2002-03-13 Thread Jay Cox
... data Peano = Zero | Succ (Peano) sumpeano blah (Succ x) = sumpeano (Succ blah) x sumpeano blah Zero = blah sumpeano not strict on first argument. define instance Num for Peano. I dont even know if you could talk about strictness in either argument with church numerals. (and I'm to l

Strictness (was: Is this tail recursive?)

2002-03-14 Thread Brian Huffman
At 22:47 13/03/02 -0600, Jay Cox wrote: >Perhaps what could be done about this strictness business is to make a >kind of strictness annotation. Perhaps something that says (force the >second argument of function F before every call to F (including any time F >calls itself)). >

[Haskell] bug in language definition (strictness)

2009-08-06 Thread Malcolm Wallace
It has been brought to my attention (as errata editor of the revised H'98 report) that there is a bug in the language definition, concerning strictness annotations on datatypes. In section 4.2.1, the translation of strict components of a data constructor is defined as (\ x1 .

guiding strictness/lazyness through the program

2001-03-13 Thread andreas.marth
Hallo! Does anybody know of a paper that describes ways how to force strict evaluation at some places and lazy evaluation at others? And I am also interested in a guideline when to use strict evaluation and when lazy. Any pointers appreciated! Thanks, Andreas __

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-04 Thread Malcolm Wallace
John Meacham <[EMAIL PROTECTED]> writes: > ghc: > putChar _|_ -> _|_ > putStr _|_ -> valid IO () > > hugs: > putChar _|_ -> valid IO () > putStr _|_ -> valid IO () I think it comes down to buffering behaviour doesn't it? Should the character be evaluated when it is added to the output buffer,

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-04 Thread Malcolm Wallace
I wrote: > > ghc: > > putChar _|_ -> _|_ > > > > hugs: > > putChar _|_ -> valid IO () > > I think it comes down to buffering behaviour doesn't it? Having reviewed the IRC logs, I see I was talking nonsense. You want to be able to store a closure for (putChar undefined) in a data structure, whi

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-04 Thread Duncan Coutts
On Tue, 2005-10-04 at 13:46 +0100, Malcolm Wallace wrote: > I wrote: > > > > ghc: > > > putChar _|_ -> _|_ > > > > > > hugs: > > > putChar _|_ -> valid IO () > > > > I think it comes down to buffering behaviour doesn't it? > > Having reviewed the IRC logs, I see I was talking nonsense. > > You

RE: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Simon Marlow
gt; > Looking at GHC's library code we see that it is indeed forcing the > char early: > > hPutChar :: Handle -> Char -> IO () > hPutChar handle c = > c `seq` do > ... Fixed. However, I have a hunch that there are a *lot* of library functions whose strictness is

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Ross Paterson
On Wed, Oct 05, 2005 at 03:22:29PM +0100, Simon Marlow wrote: > Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; return > ()) as interchangeable, which is naughty, and people have occasionally > noticed, but the benefits can sometimes be huge. What's wrong with identifying them?

RE: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Simon Marlow
On 05 October 2005 15:46, Ross Paterson wrote: > On Wed, Oct 05, 2005 at 03:22:29PM +0100, Simon Marlow wrote: >> Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; >> return ()) as interchangeable, which is naughty, and people have >> occasionally noticed, but the benefits can some

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Ross Paterson
On Wed, Oct 05, 2005 at 04:01:09PM +0100, Simon Marlow wrote: > No, of course I don't expect the monad laws to hold :) > > But the intended meaning of > > (do _|_; return () :: IO ()) `seq` True > > is True, not _|_, right? This isn't made explicit in the report, but > it's how we all

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Wolfgang Jeltsch
Am Mittwoch, 5. Oktober 2005 16:22 schrieb Simon Marlow: > [...] > Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; return > ()) as interchangeable, which is naughty, and people have occasionally > noticed, but the benefits can sometimes be huge. It is this distinction > that mak

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Wolfgang Jeltsch
Am Mittwoch, 5. Oktober 2005 16:22 schrieb Simon Marlow: > [...] > Basically anything for which the report doesn't give the full code, except > of course primitives which usually must be strict. Why must primitives be strict? I wouldn't consider putChar undefined an undefined action. In my opi

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Wolfgang Jeltsch
Am Mittwoch, 5. Oktober 2005 17:01 schrieb Simon Marlow: > On 05 October 2005 15:46, Ross Paterson wrote: > > On Wed, Oct 05, 2005 at 03:22:29PM +0100, Simon Marlow wrote: > >> Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; > >> return ()) as interchangeable, which is naughty, an

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Lennart Augustsson
Wolfgang Jeltsch wrote: Am Mittwoch, 5. Oktober 2005 16:22 schrieb Simon Marlow: [...] Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; return ()) as interchangeable, which is naughty, and people have occasionally noticed, but the benefits can sometimes be huge. It is this

RE: [Haskell] strictness of putChar: report incomplete?

2005-10-06 Thread Simon Marlow
On 05 October 2005 17:05, Lennart Augustsson wrote: > Wolfgang Jeltsch wrote: >> Am Mittwoch, 5. Oktober 2005 16:22 schrieb Simon Marlow: >> >>> [...] >> >> >>> Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; >>> return ()) as interchangeable, which is naughty, and people have

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-06 Thread Lennart Augustsson
Simon Marlow wrote: I agree with you. And that is how it used to be, but then some people didn't think that was convenient enough so now we are stuck with a seq that (IMHO) stinks. :) Having a seq that works on anything is occasionally very useful for fixing space leaks, and the type class ve

Re: Strictness (was: Is this tail recursive?)

2002-03-14 Thread Andrew Butterfield
At 22:47 13/03/02 -0600, Jay Cox wrote: >Perhaps what could be done about this strictness business is to make a >kind of strictness annotation. Perhaps something that says (force the >second argument of function F before every call to F (including any time F >calls itself)). >

Re: Strictness (was: Is this tail recursive?)

2002-03-14 Thread matt hellige
trict on first argument. > define instance Num for Peano. > > I dont even know if you could talk about strictness in either argument > with church numerals. (and I'm to lazy to remind myself what a church > numeral looks like precisely so that I could find out.) > i su

Re: Strictness (was: Is this tail recursive?)

2002-03-14 Thread Jay Cox
On Thu, 14 Mar 2002, Andrew Butterfield wrote: > I think the Clean type system does stuff like this - it certainly supports > strictness analysis and annotations: > - see http://www.cs.kun.nl/~clean/ for more details Thanks to both you and to Bernard James POPE for the repl

Non-strictness vs. laziness (was RE: Sisal)

1999-09-24 Thread Frank A. Christoph
Joe Fasel wrote: > Actually, I think we were originally thinking of laziness, rather > than nonstrictness, and weren't considering languages like Id as > part of our domain, but Arvind and Nikhil (quite correctly) convinced > us that the semantic distinction of strictness ver

[Haskell] why no strictness annotations in labelled fields?

2004-12-01 Thread S. Alexander Jacobson
Is there a good reason one can't do: data Foo = Foo {bar::!String} -Alex- __ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com ___ Haskell mailing list [EMAIL PROTECTED] http:/

RE: Non-strictness vs. laziness (was RE: Sisal)

1999-09-24 Thread Frank A. Christoph
t; >> us that the semantic distinction of strictness versus nonstrictness > >> should be our concern, rather than the operational notions of > >> eagerness and laziness. > > "Frank A. Christoph" <[EMAIL PROTECTED]>: > >Please elucidate. Where d

  1   2   >