Laziness

2003-08-02 Thread Dominic Steinitz
   hLen   = length $ head hs I would have thought laziness would allow the compiler to know that hs would contain at least one element and therefore calculate hLen.   Dominic.    

unneeded laziness

1997-11-08 Thread S.D.Mechveliani
There was recently some discussion on the subject of un-needed laziness. I thank Jon Mountjoy <[EMAIL PROTECTED]>, Simon P.Jones <[EMAIL PROTECTED]>, Sietse Achterop <[EMAIL PROTECTED]> for their remarks and guidance. Thus Jon Mountjoy gives a literature reference conc

Re: Laziness

2003-08-02 Thread Jon Fairbairn
this does > > test l = >hs > where > hs = map (\x -> [x]) (0:[1..abs(l `div` hLen)]) > hLen = length $ head hs > > I would have thought laziness would allow the compiler to > know that hs would contain at least one element and > therefore calc

Reflections on Laziness

1996-05-08 Thread Frank Christoph
Haskell has enough other worthwhile features that it's sometimes easy to forget one of the most important, laziness, especially if, like me, you started programming Haskell before SML. Not so long back, I finally got around to reading John Hughes famous paper, "Why Functional P

foldl, unneeded laziness

1998-06-29 Thread S.D.Mechveliani
n foldl(Strict) and related things. Concerning the un-needed laziness, we, probably, have to think about its cost bound. The evaluation cost is nR + C*nA, where nR is the number of "reduction steps", nA number of the cell allocations (for new data). C

`partition', laziness policy

2000-01-20 Thread S.D.Mechveliani
iced. The questions are: (1) What laziness freedom is allowed for a Standard function implementation? (2) Should Haskell consider also the stronger equivalence relation on programs? Example for (1). For the standard description partition p xs = (filter p xs, filter (not

laziness in IO

2003-01-08 Thread Amanda Clare
How can I recursively collect a list of things while in the IO monad, and return the list lazily as it's constructed rather than waiting until they've all been collected? Perhaps an example will make things clearer: main = do xs <- getStrings putStrLn (head xs) getStrings = do x <- g

evil laziness in iteration

1997-10-31 Thread S.D.Mechveliani
On the evil iteration laziness. Do not panic. - There were a couple of messages from me on the subject of the evil treating of iteration in lazy evaluation. The worst examples are like this: let sum xs = foldl (+) 0 xs ::Int in sum [1

laziness and functional middleware

1998-06-12 Thread S. Alexander Jacobson
Laziness appears to have a wierd interaction with IO. According to the docs, you should add two numbers from the user like this: > main = do > hSetBuffering stdout NoBuffering > putStr "Enter an integer: " > x1 <- r

Re: `partition', laziness policy

2000-01-21 Thread Fergus Henderson
On 20-Jan-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > The questions are: > > (1) What laziness freedom is allowed for a Standard function > implementation? I think the answer to that is "none". Implementations are free to optimize code, so long as the ope

Re: `partition', laziness policy

2000-01-20 Thread Koen Claessen
S.D.Mechveliani wrote: | partition1 p xs = (filter p xs, filter (not . p) xs) : | and optimized implementations, like, say, | | partition2 p = foldr (\x (ys, zs) -> if p x then (x:ys,zs) else (ys,x:zs)) |([],[]) | | may be not equivalent. Why is this an opti

Detail: laziness in show

2001-02-09 Thread Patrik Jansson
I just uncountered an interesting example of (hidden) laziness - here is a very short session with hugs (February 2000): Prelude> undefined :: String " Program error: {undefined} Note the starting double quote on the line before the error! In a more complicated context this puzzled

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

Re: laziness in IO

2003-01-08 Thread Hal Daume III
The following works for me: import IOExts main = do xs <- unsafeInterleaveIO getStrings putStrLn (head xs) getStrings = do x <- getLine if x == "stop" then return [] else do xs <- unsafeInterleaveIO getStrings; return (x:xs) in this particular case, the unsafeInterleaveIO

Re: laziness in IO

2003-01-08 Thread S.M.Kahrs
I don't think you can do what you want to using standard lists, not without some dirty trickery... But you can define a datatype for such a purpose which would essentially have to put the tail into the Monad. Disadvantage: you would have to redo lots of the list stuff yourself. I had once started

Re: laziness in IO

2003-01-09 Thread Christopher Milton
Hal's solution reminds me of the paper by Levent Erkök and John Launchbury: Recursive monadic Bindings: Technical Development and Details. http://www.cse.ogi.edu/PacSoft/projects/rmb/mfixTR.pdf One of their examples uses MonadRec and IOExts. webpage: Value recursion in Monadic Computations (a.k.a.

learning to love laziness

2003-09-24 Thread Norman Ramsey
Consider the following Haskell function: > asPair x = (fst x, snd x) This function has type forall a b. (a, b) -> (a, b) and is almost equivalent to the identity function, except it can be used to make programs terminate that might otherwise fall into a black hole. My students are extremely myst

Re: evil laziness in iteration

1997-11-05 Thread Simon L Peyton Jones
Sergey Thanks for your various messages. I've explained your results below. You are right to say that it's hard to be sure what optimisations will happen when; arguably that's a bad shortcoming of functional programming (especially the lazy sort). Profiling tools help a bit. I think, though, tha

Re: laziness and functional middleware

1998-06-17 Thread Simon L Peyton Jones
(dropWhile ('\n'/=) text)) > > But this code doesn't work. It prints all the text and then waits for > input. Shouldn't laziness guarantee that addTwo doesn't print "Enter > another integer" until the user enters the first integer? (that is what &g

Re: laziness and functional middleware

1998-06-17 Thread S. Alexander Jacobson
On Wed, 17 Jun 1998, Simon L Peyton Jones wrote: > What is "Strict". If you said (x `seq` ask2) instead > of (ask2 (Strict x)) then you should get the behaviour you expect. "x `seq` ask2" didn't worth but after a little more research, "ask2 `strict` x" did. The general question is whether it i

Re: laziness and functional middleware

1998-06-17 Thread Hans Aberg
At 07:54 +0100 98/06/17, Simon L Peyton Jones wrote: >> Ideally, I would like to write cgifunctions of type: >> >> myCGIFunction:: [HTTPRequest]->[DatabaseVersion]-> >> ([HTTPResponse],[DatabaseChanges]) >> >> HTTPRequests come from _middleware_ that recieves http requests fro

Re: laziness and functional middleware

1998-06-18 Thread Alastair Reid
> 1. What implementations are supporting concurrent Haskell? AFAIK only GHC and Hugs. > What modules do I have to import to use it? Read the Hugs-GHC documentation in hugs/doc > Hugs claims to support it, but I can't figure out how to engage it. It's on all the time. The implementation cost

Re: laziness and functional middleware

1998-06-18 Thread S. Alexander Jacobson
On Wed, 17 Jun 1998, Hans Aberg wrote: > But I found it rather difficult to implement this style with POSIX (Java) > threads: It is hard to guarantee that the computations does not hang. What > I needed was to be able to guarantee that certain sequences in the > implementation cannot the halted

Re: laziness and functional middleware

1998-06-19 Thread Alastair Reid
> On Thu, 18 Jun 1998, Alastair Reid wrote: > > Read the Hugs-GHC documentation in hugs/doc > > Can you give me a more direct pointer? I am not finding it in my docs. hugs/docs/libs-html/libs.html (which is linked to by hugs/docs/index.html) Alastair: > > Hugs/GHC runs everything in a single OS

Re: laziness and functional middleware

1998-06-18 Thread S. Alexander Jacobson
On Thu, 18 Jun 1998, Alastair Reid wrote: > > What modules do I have to import to use it? > > Read the Hugs-GHC documentation in hugs/doc Can you give me a more direct pointer? I am not finding it in my docs. > > Also, if you are using system > > threads then you get the additional benefit

Re: laziness and functional middleware

1998-06-19 Thread Simon L Peyton Jones
> The paper says: > "We are working on a distributed implementation of Concurrent Haskell. > Once nice property of MVars is that they seem relatively easy to implement > in a distributed setting..." > I assume that they are not referring to GPH here. > (I was surprised that at this statement giv

Re: Detail: laziness in show

2001-02-09 Thread Fergus Henderson
On 09-Feb-2001, Patrik Jansson <[EMAIL PROTECTED]> wrote: > I just uncountered an interesting example of (hidden) laziness - here is > a very short session with hugs (February 2000): > > Prelude> undefined :: String > " > Program error: {undefined} > > Note

Re: seq / strictness and laziness

2001-11-12 Thread Dean Herington
iles get read in but the processing > is delayed by laziness, and the files are being retained. It looks > something like this (after simplification): > > main = do > result <- foldM countAFile initialcounts fileNameList > prettyprint result > > countAFile o

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: 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: learning to love laziness

2003-09-24 Thread Richard Nathan Linger
On Wed, 24 Sep 2003, Norman Ramsey wrote: > Consider the following Haskell function: > > > asPair x = (fst x, snd x) > > This function has type forall a b. (a, b) -> (a, b) > and is almost equivalent to the identity function, except it > can be used to make programs terminate that might otherw

Re: learning to love laziness

2003-09-24 Thread Iavor Diatchki
hello, Richard Nathan Linger wrote: On Wed, 24 Sep 2003, Norman Ramsey wrote: Consider the following Haskell function: asPair x = (fst x, snd x) This function has type forall a b. (a, b) -> (a, b) and is almost equivalent to the identity function, except it can be used to make programs termina

Re: learning to love laziness

2003-09-25 Thread Mark Tullsen
Haskell has lazy/lifted products and not true products. This "feature" is considered by many to be an unfortunate aspect of Haskell. A 2-tuple is just syntactic sugar for data Tuple2 a b = Tuple2 a b Maybe from seeing this, it's clearer why laws such as x = (fst x,snd x) do not hold. Neither

Re: learning to love laziness

2003-09-25 Thread Derek Elkins
On Thu, 25 Sep 2003 12:59:37 -0700 Mark Tullsen <[EMAIL PROTECTED]> wrote: > Haskell has lazy/lifted products and not true products. Aren't lazy products true products? What makes something a product is: fst (x,y) = x snd (x,y) = y for all x and y. This holds with lazy products but not eager

Re: learning to love laziness

2003-09-26 Thread John Hughes
On Fri, 26 Sep 2003, Derek Elkins wrote: > On Thu, 25 Sep 2003 12:59:37 -0700 > Mark Tullsen <[EMAIL PROTECTED]> wrote: > > > Haskell has lazy/lifted products and not true products. > > Aren't lazy products true products? What makes something a product is: > fst (x,y) = x > snd (x,y) = y > for al

hGetContents and laziness in file io

2001-07-23 Thread Hal Daume
Hi! I have a few laziness/performace questions regarding file io in haskell (particularly hugs, right now). I'm writing a program that basically converts file formats. The files are parse trees for natural language. So I read in one of the parse trees in the original format and write i

Help!: Using Laziness to Implement Recursive Let

1996-02-01 Thread Frank Christoph
zer in that environment and binding those values (if they succeed) before evaluating the body, but it seems like a waste to use that approach in Haskell which, after all, could theoretically do all this for me, via laziness. Any helpful comments would be very much appreciated. Frank Christoph [EM

Full laziness (was Re: Q: hugs behavior...)

1999-08-26 Thread Mike Thyer
just about to write in my thesis that current functional languages weren't fully lazy. Would this be an over simplification of the issue, are there some options I can pass that make any of the Haskell implementations fully lazy? cheers, Mike Simon Marlow wrote: > > I think that the tr

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

Re: interesting example of laziness/ghc optimisation

2001-02-28 Thread Laszlo Nemeth
* * * Ketil Malde <[EMAIL PROTECTED]> wrote: > > runRandom last max num > > | num > 1 = runRandom (fst new) max (num-1) > > | otherwise = snd new > > What's the difference between the pipe-syntax, and a case statement, > i.e. writing the function as > > runRandom last max num = case n

Re: hGetContents and laziness in file io

2001-07-23 Thread Thomas Hallgren
Hi, My guess is that there is a space leak in your program. In both function convert and parseAll, there are references (the variable ulf) to the contents of the input file, and they will probably not be released until the functions return (unless you use a compiler that is clever enough to d

Re: hGetContents and laziness in file io

2001-07-24 Thread Hal Daume
Okay, I understand the problem. I would do something like the solution you propose, except that in the input file, trees span multiple lines. So the input file looks something like: (:cat S :subs ((() (:cat NP :subs ((() (:surf "John") (() (:cat VP :subs (

[Haskell] Laziness and the IO Monad (randomness)

2007-03-01 Thread Dave Tapley
;= \y -> return (x:y) However this latter case gets stuck in an infinite loop, terminating on a stack overflow. My question asks why this is the case, when laziness should ensure only the first 10 cases need to be computed. If anyone wishes to suggest another wa

Re: Help!: Using Laziness to Implement Recursive Let

1996-02-05 Thread Frank Christoph
(Sorry for the three messages in a row.) BTW, the way I have this working now is to evaluate all initializers first, check for errors, if there are no errors add them all to the environment, then use an update function which update :: Env -> Datum -> Datum which is the identity

Re: Help!: Using Laziness to Implement Recursive Let

1996-02-05 Thread Frank Christoph
Just wanted to mention (in case anyone noticed) that there is an error in the following code: > errQ :: [Robust r e] -> [r] -> Robust [r] e > errQ (OK x:xs)acc = errQ xs (x : acc) > errQ (Throw x:xs) acc = throw x > errQ [] acc = ok acc It will

Re: Help!: Using Laziness to Implement Recursive Let

1996-02-05 Thread Frank Christoph
> 1. It is supposed to be considered an error if an initializer references > the value of any binder variable. This implementation does indeed respect Why do you say that? I thought that "letrec" semantics was precisely setup to allow mutually recursive references within initial

RE: Full laziness (was Re: Q: hugs behavior...)

1999-08-27 Thread Adrian Hey
On Fri 27 Aug, Simon Peyton-Jones wrote: > > func n = map (func' n) [1..10] > > func' x y = nfib x > > There isn't a free subexpression to lift out of func. I had always imagined that in a fully lazy language a function like Mike Thyers example would get transformed into something like this..

RE: Full laziness (was Re: Q: hugs behavior...)

1999-08-27 Thread Simon Peyton-Jones
There's a whole chapter on full laziness in my book; and a paper in Software Practice and Experience A modular fully-lazy lambda lifter in Haskell, SL Peyton Jones and D Lester, Software Practice and Experience 21(5), May 1991, pp479-506. The latter is available on my publications page

Re: Full laziness (was Re: Q: hugs behavior...)

1999-08-27 Thread Mike Thyer
Simon Peyton-Jones wrote: > > func n = map (func' n) [1..10] > > func' x y = nfib x > > There isn't a free subexpression to lift out of func. No, but as Adrian Hey quite correctly points out there is a free subexpression in func' that can be lifted out of its enclosing (\y->...). > Try this >

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

1999-09-24 Thread Frank A. Christoph
Bjorn Lisper wrote: > >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 &g

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

1999-09-24 Thread Bjorn Lisper
>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

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

1999-09-24 Thread Joe Fasel
Frank Christoph wrote, | Ah, right. Someone mentioned just recently (I forget who---sorry) that | nothing in the Report forces a Haskell implementation to use call-by-need. I | guess this is a manifestation of the change of direction, from laziness to | non-strictness...? My point was meant to

Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-01 Thread David Brown
Dave Tapley wrote: > This code show a trivial case where randomness (and hence the IO > monad) is not used and the first 10 elements of the produced list > are printed: You don't need the IO monad to achieve pseudy-randomness. Why not use 'randoms' from System.Random (or 'randomRs' for a range).

Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-01 Thread Taral
On 3/1/07, Dave Tapley <[EMAIL PROTECTED]> wrote: My question asks why this is the case, when laziness should ensure only the first 10 cases need to be computed. Basically, because the IO monad is strict, not lazy. If you want laziness, don't use the IO monad. -- Taral <[E

Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-01 Thread Paul Johnson
David Brown wrote: Dave Tapley wrote: This code show a trivial case where randomness (and hence the IO monad) is not used and the first 10 elements of the produced list are printed: You don't need the IO monad to achieve pseudy-randomness. Why not use 'randoms' from System.Random (or

Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-02 Thread Joe Thornber
On 01/03/07, Dave Tapley <[EMAIL PROTECTED]> wrote: My question asks why this is the case, when laziness should ensure only the first 10 cases need to be computed. Just to clarify some of the other answers you've got. Saying the IO monad is strict isn't the whole picture, af

Pattern guards vs. case (was, unfortunately :Re: interesting example of laziness/ghc optimisation)

2001-03-01 Thread Ketil Malde
(Apologies, I forgot to change the subject) Laszlo Nemeth <[EMAIL PROTECTED]> writes: > * * * Ketil Malde <[EMAIL PROTECTED]> wrote: > There is no difference. The 'pipe-syntax' (or pattern guards) gets > desugared (by the pattern matching compiler) to case statements i.e.: > runRandom = \ las

Re: Pattern guards vs. case (was, unfortunately :Re: interesting exampleof laziness/ghc optimisation)

2001-03-01 Thread Johannes Waldmann
> But if you want to be really weird you can write something > like (I haven't typed this in): > > f x | (Foo _) == x = > f x | (Bar _) == x = no, you can't, e. g. hugs (Feb 2000) says Prelude> let f x | Just 4 == x = 0 in f (Just 4) 0 Prelude> let f x | Just _ == x = 0 in f (Just 4) ERROR: I

Re: Pattern guards vs. case (was, unfortunately :Re: interesting exampleof laziness/ghc optimisation)

2001-03-01 Thread Laszlo Nemeth
* * * Johannes Waldmann wrote: > > But if you want to be really weird you can write something > > like (I haven't typed this in): > > > > f x | (Foo _) == x = > > f x | (Bar _) == x = > > no, you can't, e. g. hugs (Feb 2000) says > > Prelude> let f x | Just 4 == x = 0 in f (Just 4) > 0 > Prel

Re: Pattern guards vs. case (was, unfortunately :Re: interesting example of laziness/ghc optimisation)

2001-03-01 Thread John Meacham
On Thu, Mar 01, 2001 at 09:40:48AM +0100, Ketil Malde wrote: > > (Apologies, I forgot to change the subject) > > Laszlo Nemeth <[EMAIL PROTECTED]> writes: > > > * * * Ketil Malde <[EMAIL PROTECTED]> wrote: > > > There is no difference. The 'pipe-syntax' (or pattern guards) gets > > desugared (

Re: Pattern guards vs. case (was, unfortunately :Re: interesting example of laziness/ghc optimisation)

2001-03-01 Thread Laszlo Nemeth
* * * Ketil Malde <[EMAIL PROTECTED]> wrote: > ut - the converse is not true, is it? I can write > > ... = case foo of >(Foo f) -> ... >(Bar b) -> ... > > ut I can't express that as a pattern-guarded expression, can I? You probably have already seen John's

Re: Pattern guards vs. case (was, unfortunately :Re: interesting example of laziness/ghc optimisation)

2001-03-02 Thread Marcin 'Qrczak' Kowalczyk
Thu, 1 Mar 2001 20:25:28 +0900 (KST), Laszlo Nemeth <[EMAIL PROTECTED]> pisze: > > Prelude> let f x | Just _ == x = 0 in f (Just 4) > > ERROR: Illegal `_' in expression > > So it works with (Just 4), but it doesn't with (Just _)? 'Just _ == x' must be an exppression. '_' is a pattern but not an