Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Yuras Shumovich
> -- Původní zpráva -- > Od: Corentin Dupont > Datum: 25. 12. 2012 > Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation > > " > > Great, with me compiled with ghc -threaded the bug shows up. > > However, runnning "main" in ghci do

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
aviour has been confirmed? Tim -- Původní zpráva -- Od: Corentin Dupont Datum: 25. 12. 2012 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation " Great, with me compiled with ghc -threaded the bug shows up. However, runnning "main" in ghci doesn't show t

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
. I've > narrowed this down and filed a bug report here: > > http://hackage.haskell.org/trac/ghc/ticket/7528 > > Timothy > > -- Původní zpráva -- > Od: Yuras Shumovich > > Datum: 24. 12. 2012 > Předmět: Re: [Haskell-cafe] multi-thread and

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
Hi Brandon, indeed in my example if you add: *b <- evaluate a* after the definition of "a" it works. However, in my original program it doesn't work, I suppose because I interpret the user submitted code (here "*let (a::String) = a" * for the example) via Hint and Hint-server, and the interpretati

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
multi-thread and lazy evaluation "On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote: > The real question is, does this mean that GHC is stopping the world every > time it puts an MVar? No, GHC rts only locks the MVar itself. See here: http://hackage.haskell.org/trac

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Yuras Shumovich
On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote: > The real question is, does this mean that GHC is stopping the world every > time it puts an MVar? No, GHC rts only locks the MVar itself. See here: http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358 Yuras ___

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread timothyhobbs
The real question is, does this mean that GHC is stopping the world every time it puts an MVar? Tim -- Původní zpráva -- Od: Brandon Allbery Datum: 24. 12. 2012 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation " On Mon, Dec 24, 2012 at 8:45 AM, Corentin D

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Brandon Allbery
On Mon, Dec 24, 2012 at 8:45 AM, Corentin Dupont wrote: > *execBlocking :: MVar (Maybe MyData) -> IO () > execBlocking mv = do >let (a::String) = a >--If you uncomment the next line, it will work >--putStrLn $ show a >putMVar mv (Just $ MyData a "toto")* > It's laziness, yes; you

Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Corentin Dupont
Hint. The user-submitted programs are used to modify > a state held in a TVar. > As of course those user-submitted programs can't be trusted, I'm trying to > protect them, like in Mueval. > I installed a watchdog to monitor and kill the user's thread if it doesn't &g

[Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Corentin Dupont
installed a watchdog to monitor and kill the user's thread if it doesn't finish. However it doesn't work properly, due to lazy evaluation I believe. I made a little exemple to illustrate the problem. -> The following program doesn't terminate, but if you uncomment the &quo

[Haskell-cafe] Empirically comparing strict vs. lazy evaluation

2012-10-29 Thread Kristopher Micinski
Hello Haskellers! I wonder if you know of benchmarks that attempt to compare, empirically, lazy vs. eager evaluation. Pointers to papers and/or code would be most appreciated. Our group (at UMD) is working on a paper that develops some technology for lazy programs, and we would like to choose be

Re: [Haskell-cafe] Haskell seems setup for iterative numerics; i.e. a standard example is Newton's method where lazy evaluation ...

2012-09-05 Thread Carter Schonwald
in the mean time I suggest using Hmatrix then :) On Wed, Sep 5, 2012 at 4:10 PM, KC wrote: > The REPA package/library doesn't have LU factorization, eigenvalues, etc. > > > On Wed, Sep 5, 2012 at 12:59 PM, Carter Schonwald > wrote: > > Hello KC, > > you should check out the Repa library then an

Re: [Haskell-cafe] Haskell seems setup for iterative numerics; i.e. a standard example is Newton's method where lazy evaluation ...

2012-09-05 Thread KC
The REPA package/library doesn't have LU factorization, eigenvalues, etc. On Wed, Sep 5, 2012 at 12:59 PM, Carter Schonwald wrote: > Hello KC, > you should check out the Repa library then and see how it works for you. > Cheers > -Carter > > On Wed, Sep 5, 2012 at 12:46 PM, KC wrote: >> >> separ

Re: [Haskell-cafe] Haskell seems setup for iterative numerics; i.e. a standard example is Newton's method where lazy evaluation ...

2012-09-05 Thread Carter Schonwald
Hello KC, you should check out the Repa library then and see how it works for you. Cheers -Carter On Wed, Sep 5, 2012 at 12:46 PM, KC wrote: > separates control from computation. > > It seems as if Haskell would be better for iterative matrix methods > rather than direct calculation. > > -- > --

[Haskell-cafe] Haskell seems setup for iterative numerics; i.e. a standard example is Newton's method where lazy evaluation ...

2012-09-05 Thread KC
separates control from computation. It seems as if Haskell would be better for iterative matrix methods rather than direct calculation. -- -- Regards, KC ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/ha

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Albert Y. C. Lai
On a tangent, not doing IO, but food for thought: {-# LANGUAGE FlexibleContexts #-} import Control.Monad.State.Lazy as N import Control.Monad.State.Strict as S gen :: (MonadState [()] m) => m () gen = do gen modify (() :) many = take 3 (N.execState gen []) none = take 3 (S.execState gen []

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 6:10 PM, Antoine Latter wrote: > > You could use a different type: > >> type IOStream a = (a, IO (IOStream a)) > >> unfold :: ([a] -> IO a) -> IO (IOStream a) >> unfold f = >>     let go prev = do >>           next <- f prev >>           return (next, go (next:prev)) >>    

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Antoine Latter
On Tue, May 31, 2011 at 2:49 PM, Scott Lawrence wrote: > I was under the impression that operations performed in monads (in this > case, the IO monad) were lazy. (Certainly, every time I make the > opposite assumption, my code fails :P .) Which doesn't explain why the > following code fails to ter

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
Apparently: Prelude> let r = (fmap (1:) r) :: IO [Integer] Prelude> fmap (take 5) r *** Exception: stack overflow Thanks - I'll just have to stay out of IO for this, then. On Tue, May 31, 2011 at 17:05, Stephen Tetley wrote: > 2011/5/31 Scott Lawrence : > >> Evaluation here also doesn't termina

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Stephen Tetley
2011/5/31 Scott Lawrence : > Evaluation here also doesn't terminate (or, (head $ unfoldM (return . > head)) doesn't), although I can't figure out why. fmap shouldn't need to > fully evaluate a list to prepend an element, right? I'm afriad fmap doesn't get to choose - if the monad is strict then b

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 22:35:26, Yves Parès wrote: > He intended to show that, indeed, it is not, or else side-effects would > never be performed On the other hand, IO is lazy in the values it produces. Going with the IO a = State RealWorld a fiction, IO is state-strict but value-lazy. The side-e

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:48 PM, Artyom Kazak wrote: > > Oh, sorry. I was unclear. I have meant "assuming IO is lazy", as Yves > wrote. Ah, ok. That makes more sense. > > And saying "some hacks" I meant unsafeInterleaveIO, which lies beneath > the laziness of, for example, getContents. Which explains w

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Gregory Crosswhite
On 5/31/11 12:49 PM, Scott Lawrence wrote: I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. Whether they are lazy or not depends entirely on the definition of the monad. For example, if you look up the ST and State monads you will find th

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Scott Lawrence писал(а) в своём письме Tue, 31 May 2011 23:29:49 +0300: On 05/31/2011 04:20 PM, Artyom Kazak wrote: Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1 As x is never needed, launchMissiles will never execute. It obviously

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Yves Parès
No, I think Artyom meant "assuming IO is lazy". He intended to show that, indeed, it is not, or else side-effects would never be performed 2011/5/31 Scott Lawrence > On 05/31/2011 04:20 PM, Artyom Kazak wrote: > > Suppose iRecurse looks like this: > > iRecurse = do > > x <- launchMissiles

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Anthony Cowley
On Tue, May 31, 2011 at 3:49 PM, Scott Lawrence wrote: > I was under the impression that operations performed in monads (in this > case, the IO monad) were lazy. (Certainly, every time I make the > opposite assumption, my code fails :P .) Which doesn't explain why the > following code fails to ter

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
On 05/31/2011 04:20 PM, Artyom Kazak wrote: > Suppose iRecurse looks like this: > iRecurse = do > x <- launchMissiles > r <- iRecurse > return 1 > > As x is never needed, launchMissiles will never execute. It obviously is > not what is needed. Prelude> let launchMissiles = putStrLn

Re: [Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Artyom Kazak
Suppose iRecurse looks like this: iRecurse = do x <- launchMissiles r <- iRecurse return 1 As x is never needed, launchMissiles will never execute. It obviously is not what is needed. But in Haskell, standart file input|output is often lazy. It's a combination of buffering and

[Haskell-cafe] Lazy Evaluation in Monads

2011-05-31 Thread Scott Lawrence
I was under the impression that operations performed in monads (in this case, the IO monad) were lazy. (Certainly, every time I make the opposite assumption, my code fails :P .) Which doesn't explain why the following code fails to terminate: iRecurse :: (Num a) => IO a iRecurse = do recur

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Daniel Fischer
On Thursday 17 March 2011 13:05:33, Tillmann Rendel wrote: > Looks like I need an email client with ghc integration. That would be awesome. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Tillmann Rendel
Hi, Daniel Fischer wrote: Let's look at the following code: countdown n = if n == 0 then 0 else foo (n - 1) s/foo/countdown/ presumably if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1)) s/foo/countdown'/ Yes to both substitutions. Looks like I need

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 22:03:51, Yves Parès wrote: > Can a type signature give you a hint about whether a function evaluates > some/all of its arguments (i.e. is strict/partially strict/lazy), or do > you have to look at the implementation to know? Cheating, with GHC, a magic hash tells you it

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 21:44:36, Tillmann Rendel wrote: > My point is that the call to map is in tail position, because it is > the last thing the function (\_ -> map f xs ()) does. So it is not a > tail-recursive call, but it is a tail call. Mmmm, okay, minor terminology mismatch, then. M

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
> And that's what, to my knowledge, is impossible with tail recursion. A tail > recursive map/fmap would have to traverse the entire list before it could return anything. Now that you say it, yes, you are right. Tail recursion imposes strictness, since only the very last call can return something

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
Hi, Daniel Fischer wrote: data EvaluatedList a = Cons a (List a) | Empty type List a = () -> EvaluatedList a map :: (a -> b) -> (List a -> List b) map f xs = \_ -> case xs () of Cons x xs -> Cons (f x) (\_ -> map f xs ())

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 20:02:54, Yves Parès wrote: > > Yes, and a tail-recursive map couldn't run in constant space > > Yes, I meant "if you are consuming it just once immediately". > And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have t

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Henning Thielemann
On Wed, 16 Mar 2011, Daniel Fischer wrote: Tail recursion is good for strict stuff, otherwise the above pattern - I think it's called guarded recursion - is better, have the recursive call as a non-strict field of a constructor. In http://haskell.org/haskellwiki/Tail_recursion it is also

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
2011/3/16 Daniel Fischer > On Wednesday 16 March 2011 18:31:00, Yves Parès wrote: > > Hello, > > > > A question recently popped into my mind: does lazy evaluation reduce the > > need to "proper" tail-recursion? > > I mean, for instance : > > >

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 18:31:00, Yves Parès wrote: > Hello, > > A question recently popped into my mind: does lazy evaluation reduce the > need to "proper" tail-recursion? > I mean, for instance : > > fmap f [] = [] > fmap f (x:xs) = f x : fmap f xs > &

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
Hi, Yves Parès wrote: A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I

[Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
Hello, A question recently popped into my mind: does lazy evaluation reduce the need to "proper" tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may

Re: [Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-07 Thread C K Kashyap
> Have you seen Potential > (http://intoverflow.wordpress.com/2010/05/21/announcing-potential-x86-64-assembler-as-a-haskell-edsl/)? > Quote: > > "The language’s goal is to provide a solid foundation for the development of > a useful (multi-tasked, multi-processor, etc) microkernel" > > Which sounds

Re: [Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-06 Thread Neil Brown
On 06/10/10 11:00, C K Kashyap wrote: My ultimate aim it to write an EDSL for x86 - as in, describe a micro-kernel in haskell, compiling and running which would generate C code ( not sure if it's even possible - but I am really hopeful). Have you seen Potential (http://intoverflow.wordpress.

Re: [Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-06 Thread C K Kashyap
On Tue, Oct 5, 2010 at 9:19 PM, steffen wrote: > Don't be to disappointed. One can always kinda fake lazy evaluation > using mutable cells. > But not that elegantly. In the example given above, all being used is > iterators as streams... this can also be expressed using lazy l

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 On 10/5/10 10:52 , C K Kashyap wrote: > And I had built up this impression that laziness distinguished Haskell > by a huge margin ... but it seems that is not the case. > Hence the disappointment. Haskell is lazy-by-default and designed ar

[Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread steffen
Don't be to disappointed. One can always kinda fake lazy evaluation using mutable cells. But not that elegantly. In the example given above, all being used is iterators as streams... this can also be expressed using lazy lists, true. But one big difference between e.g. lazy lists and iterato

[Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Ertugrul Soeylemez
ment was not on a serious note ... the thing is, I > constantly run into discussions about "why fp" with my colleagues - in > a few of such discussions, I had mentioned that Haskell is the only > well known language with lazy evaluation (IIRC, I read it somewhere or > heard it in

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
, I constantly run into discussions about "why fp" with my colleagues - in a few of such discussions, I had mentioned that Haskell is the only well known language with lazy evaluation (IIRC, I read it somewhere or heard it in one of the videos) And I had built up this impression that la

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Hemanth Kapila
> > I see ... I think I understand now. > hmmm ... I am little disappointed though - does that mean that "all > the laziness" cool stuffs can actually be done using > iterators(generators)? > As in, but for the inconvenient syntax, you can do it all in - say java? Yes. It would slightly easier in

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Brent Yorgey
= nextVal > >    } > > } > > > > I have not tested it but I think this is a fair translation of the code. > >  (For instance, by using an appropriate implementation of IBoundsCheck, I > > will be able to implement the 'relativeSqrt' functionality of

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
de. >  (For instance, by using an appropriate implementation of IBoundsCheck, I > will be able to implement the 'relativeSqrt' functionality of the example). > But this IS still a lazy evaluation. By passing an iterator instead of a > list as the third argument of the static method, I a

Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Hemanth Kapila
will be able to implement the 'relativeSqrt' functionality of the example). But this IS still a lazy evaluation. By passing an iterator instead of a list as the third argument of the static method, I achieved 'laziness'. In the example, the laziness is in the way we are iterati

[Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
Hi All, I was going through the paper's "lazy evaluation" section where the square root example is given. It occurred to me that one could implement it in a modular way with just higher order functions (without the need for lazy evaluation that is). function f (within, eps, next

Re: [Haskell-cafe] Lazy evaluation/functions

2009-12-27 Thread Erlend Hamberg
On Sunday 27. December 2009 14.16.15 michael rice wrote: > I've seen the terms "lazy evaluation" and "lazy function." Is this just > lazy language or are both these terms valid? In some languages, like Oz, one can have lazy functions even though the default is

Re: [Haskell-cafe] Lazy evaluation/functions

2009-12-27 Thread Tom Davie
Lazy evaluation is an evaluation strategy that gives non-strict semantics. A lazy function I'm not sure how to define. It may be lazy language meaning a function which is non-strict in one of it's arguments. Bob On Sun, Dec 27, 2009 at 1:16 PM, michael rice wrote: > I've se

[Haskell-cafe] Lazy evaluation/functions

2009-12-27 Thread michael rice
I've seen the terms "lazy evaluation" and "lazy function." Is this just lazy language or are both these terms valid? Michael ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread George Pollard
On Tue, 2009-02-10 at 08:03 +0100, Thomas Davie wrote: > On 10 Feb 2009, at 07:57, Max Rabkin wrote: > > > On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki > > wrote: > >> I 0 * _ = I 0 > >> I x * I y = I (x * y) > > > > Note that (*) is now non-commutative (w.r.t. _|_). Of course, that'

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Thomas Davie
On 10 Feb 2009, at 07:57, Max Rabkin wrote: On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki wrote: I 0 * _ = I 0 I x * I y = I (x * y) Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's what we need here, but it means that the "obviously correct" transformation o

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Max Rabkin
On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki wrote: > I 0 * _ = I 0 > I x * I y = I (x * y) Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's what we need here, but it means that the "obviously correct" transformation of > foo x = if x == 0 then 0 else foo (x -

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Iavor Diatchki
Hi, Just for fun, here is the code that does this: newtype Int' = I Int deriving Eq instance Show Int' where show (I x) = show x instance Num Int' where I x + I y = I (x + y) I 0 * _ = I 0 I x * I y = I (x * y) I x - I y = I (x - y) abs (I x) = I (abs x) s

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Jochem Berndsen
Peter Padawitz wrote: > A simplied version of Example 5-16 in Manna's classical book > "Mathematical Theory of Computation": > > foo x = if x == 0 then 0 else foo (x-1)*foo (x+1) > > If run with ghci, foo 5 does not terminate, i.e., Haskell does not look > for all outermost redices in parallel. Why

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Robin Green
On Mon, 09 Feb 2009 15:10:22 +0100 Peter Padawitz wrote: > A simplied version of Example 5-16 in Manna's classical book > "Mathematical Theory of Computation": > > foo x = if x == 0 then 0 else foo (x-1)*foo (x+1) > > If run with ghci, foo 5 does not terminate, i.e., Haskell does not > look fo

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Bulat Ziganshin
Hello Peter, Monday, February 9, 2009, 5:10:22 PM, you wrote: > If run with ghci, foo 5 does not terminate, i.e., Haskell does not look > for all outermost redices in parallel. Why? For efficiency reasons? of course. if you will create new thread for every cpu instruction executed, you will defi

[Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Peter Padawitz
A simplied version of Example 5-16 in Manna's classical book "Mathematical Theory of Computation": foo x = if x == 0 then 0 else foo (x-1)*foo (x+1) If run with ghci, foo 5 does not terminate, i.e., Haskell does not look for all outermost redices in parallel. Why? For efficiency reasons? It'

Re: [Haskell-cafe] Avoiding lazy evaluation in an ErrorT computation

2008-07-07 Thread Don Stewart
Just use 'rnf', from the Control.Parallel namespace. ryani.spam: > This is the classic "exception embedded in pure value" problem with > lazy languages. There's no need for the "a" returned by "return" to > be evaluated. > > Even using "seq" isn't quite good enough: > > > boom2 = [1 `div` 0] >

Re: [Haskell-cafe] Avoiding lazy evaluation in an ErrorT computation

2008-07-07 Thread Ryan Ingram
This is the classic "exception embedded in pure value" problem with lazy languages. There's no need for the "a" returned by "return" to be evaluated. Even using "seq" isn't quite good enough: > boom2 = [1 `div` 0] ghci> doTinIO (boom2 `seq` return boom2) Right [*** Exception: divide by zero If

Re: [Haskell-cafe] Avoiding lazy evaluation in an ErrorT computation

2008-07-07 Thread Brandon S. Allbery KF8NH
On 2008 Jul 7, at 11:14, Tim Bauer wrote: My problem is that I control `doTinIO', but someone else provides the computation (T a). I cannot force callers to strictly evaluate their computations. try (Control.Exception.evaluate ...) -- ? -- brandon s. allbery [solaris,freebsd,perl,pugs,haske

[Haskell-cafe] Avoiding lazy evaluation in an ErrorT computation

2008-07-07 Thread Tim Bauer
The file below models a problem I have been trying to figure out. This file simplifies my original code, while still illustrating the problem. > import Prelude hiding (catch) > import Control.Monad.Reader > import Control.Monad.Error > import Control.Exception > import System.IO(readFile) > impor

Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Peter Padawitz
@ Miguel: Thanks for carrying out the fixpoint computation I was too lazy to do! I see: lazy evaluation programmers must not be lazy ;-) @ Josef: Oh yes, I mixed up x and y! In fact, I was confused about the semantical difference between eqrev and eqrev', although eqrev is just an iter

Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Josef Svenningsson
On Feb 6, 2008 3:06 PM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: > > On 6 Feb 2008, at 16:32, Peter Padawitz wrote: > > > Can anybody give me a simple explanation why the second definition > > of a palindrome checker does not terminate, although the first one > > does? > > > > pal :: Eq a => [a

Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Miguel Mitrofanov
On 6 Feb 2008, at 16:32, Peter Padawitz wrote: Can anybody give me a simple explanation why the second definition of a palindrome checker does not terminate, although the first one does? pal :: Eq a => [a] -> Bool pal s = b where (b,r) = eqrev s r [] eqrev :: Eq a => [a] -> [a] -> [a] ->

Re: [Haskell-cafe] lazy evaluation

2008-02-06 Thread Henning Thielemann
On Wed, 6 Feb 2008, Peter Padawitz wrote: > Can anybody give me a simple explanation why the second definition of a > palindrome checker does not terminate, although the first one does? Just another question, what about x == reverse x ? - You can still optimize for avoiding duplicate equalit

[Haskell-cafe] lazy evaluation

2008-02-06 Thread Peter Padawitz
Can anybody give me a simple explanation why the second definition of a palindrome checker does not terminate, although the first one does? pal :: Eq a => [a] -> Bool pal s = b where (b,r) = eqrev s r [] eqrev :: Eq a => [a] -> [a] -> [a] -> (Bool,[a]) eqrev (x:s1) ~(y:s2) acc = (x==y&&b,r) whe

[Haskell-cafe] Re: help understanding lazy evaluation

2007-08-23 Thread apfelmus
Ronald Guida wrote: > Can anyone tell me if I've got this right? Yes, you got. The let-statement you introduce that embodies the sharing of the argument n = 12 probably should be present in the first parts, too. But this doesn't really matter, the formalities of graph reduction vary with the

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Ronald Guida
I'm trying to understand lazy evaluation as well. I created an example for myself and I'm wondering if I've got it right. > let adder n = \x -> n + x in (map (adder 12) [1,2,3]) !! 1 So the first thing I did is draw a graph to represent my expression. (map (ad

[Haskell-cafe] Re: help understanding lazy evaluation

2007-08-23 Thread Jon Fairbairn
Stefan O'Rear <[EMAIL PROTECTED]> writes: > Indeed, you've caught on an important technical distinction. > > Lazy: Always evaluating left-outermost-first. I think most people would rather use the term "normal order¨ for that; lazy means evaluating in normal order /and/ not evaluating the same ex

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Malte Milatz
Stefan O'Rear wrote: > As is usual for mathematical things, there are many equivalent > definitions. My two favorites are: > > 1. Normal order reduction > > In the λ-calculus, lazy evaluation can be defined as the (unique up to > always giving the same answer) evaluat

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Bulat Ziganshin
Hello Xavier, Thursday, August 23, 2007, 3:08:25 AM, you wrote: > I am learning Haskell with "Programming in Haskell" (an excellent > book BTW). scheme of lazy evaluation called "graph reduction" you may consider it as repetitive replacing right parts of function d

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Stefan O'Rear
On Thu, Aug 23, 2007 at 10:00:00AM +0200, Xavier Noria wrote: > You people rock. Responses were really helpful and I understand how the > computation goes now. > > I see I need to reprogram my eyes to expect lazy evaluation in places where > I am used to one-shot results. I see

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-23 Thread Xavier Noria
You people rock. Responses were really helpful and I understand how the computation goes now. I see I need to reprogram my eyes to expect lazy evaluation in places where I am used to one-shot results. I see lazy evaluation is all around in Haskell builtins. From a formal point of view

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-22 Thread Ryan Ingram
) = x == y && xs == ys [] == [] = True _ == _ = False All other functions used are primitives. Exercise: Write out a full execution trace for n == 3 and n == 4 with the desugaring and Prelude functions given above. On 8/22/07, Xavier Noria <[EMAIL PROTECTED]> wrote: > > I am learn

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-22 Thread Derek Elkins
> > > [*] Which notation do you use for functions in text? is f() ok? > > Sure, although a little unusual for Haskell where f() means f applied > to the empty tuple. Some people use |f| (generally those who use > latex), but generally it can be inferred from the context what is a > function Nei

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-22 Thread Michael Vanier
. Hughes' paper "Why Functional Programming Matters" is a must-read for more on this. Lazy evaluation can be very tricky to wrap your head around, and there are lots of subtle issues that crop up where you think something is lazy but it's not, or you think something is strict but

Re: [Haskell-cafe] help understanding lazy evaluation

2007-08-22 Thread Neil Mitchell
particular evaluation of > factors, in particular step puzzles me. Can anyone explain how lazy > evaluation fits there? I suspect the key is the implementation of == > together with the fact that list comprehensions are lazy themselves, > is that right? Everything is lazy, to all subparts

[Haskell-cafe] help understanding lazy evaluation

2007-08-22 Thread Xavier Noria
I am learning Haskell with "Programming in Haskell" (an excellent book BTW). I have background in several languages but none of them has lazy evaluation. By now I am getting along with the intuitive idea that things are not evaluated until needed, but there's an

Re: [Haskell-cafe] Logic programming using lazy evaluation

2007-02-28 Thread Henning Thielemann
On Tue, 27 Feb 2007, Chris Kuklewicz wrote: > For an infinite number of equations you have to generate them as data at run > time. Your notation above only works for a finite set of equations known at > compile time. > > So you have a stream of equations, and each equation depends on some subset

Re: [Haskell-cafe] Logic programming using lazy evaluation

2007-02-28 Thread Henning Thielemann
Nothing, Nothing, Nothing, Just 1, ... y = [Nothing, Nothing, Just 2, ... z = [Nothing, Just 3, ... @ Features: * free choice of types of values and static type checking * free choice of rules * lazy evaluation of solutions, thus infinitely many variables and rules are possible (alth

Re: [Haskell-cafe] Logic programming using lazy evaluation

2007-02-27 Thread Chris Kuklewicz
- times 2 x2 x3 > ... > > Accessing variable values by integer identifiers means that the garbage > collector cannot free values that are no longer needed. That will always be true for potentially non-finite lists of equations. > > Thus I thought about how to solve the equations

Re: [Haskell-cafe] Logic programming using lazy evaluation

2007-02-27 Thread Henning Thielemann
On Tue, 27 Feb 2007, Ulf Norell wrote: > On 2/27/07, Henning Thielemann <[EMAIL PROTECTED]> wrote: > > > > I suspect that someone has already done this: A Haskell library which > > solves a system of simple equations, where it is only necessary to derive > > a value from an equation where all but

Re: [Haskell-cafe] Logic programming using lazy evaluation

2007-02-27 Thread Ulf Norell
On 2/27/07, Henning Thielemann <[EMAIL PROTECTED]> wrote: I suspect that someone has already done this: A Haskell library which solves a system of simple equations, where it is only necessary to derive a value from an equation where all but one variables are determined. Say You might want to c

[Haskell-cafe] Logic programming using lazy evaluation

2007-02-27 Thread Henning Thielemann
. Thus I thought about how to solve the equations by lazy evaluation. Maybe it is possible to ty the knot this way let (_,_,x0) = add 1 2 x (y0,z0,_) = times y z 20 (x1,y1,_) = add x y 5 x = alternatives [x0,x1] y = alternatives [y0,y1] z = alternatives [z0] in (solve x, solve y

Re: [Haskell-cafe] New (simple) Lazy Evaluation tutorial

2007-01-18 Thread Seth Gordon
Andrew Wagner wrote: > Hi all, > > An interesting question came up in #haskell the other day, and I took > the resulting discussion and wrapped it up into a simple tutorial for > the wiki. Since I'm quite a newbie to haskell myself, I'd appreciate > any double-checking of my logic and, of course,

[Haskell-cafe] New (simple) Lazy Evaluation tutorial

2007-01-18 Thread Andrew Wagner
Hi all, An interesting question came up in #haskell the other day, and I took the resulting discussion and wrapped it up into a simple tutorial for the wiki. Since I'm quite a newbie to haskell myself, I'd appreciate any double-checking of my logic and, of course, any other comments/suggestions.

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-06 Thread Esa Ilari Vuokko
Hi On 9/6/06, David Roundy <[EMAIL PROTECTED]> wrote: Fortunately, the undefined behavior in this case is unrelated to the lazy IO. On windows, the removal of the file will fail, while on posix systems there won't be any failure at all. The same behavior would show up if you opened the file fo

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-06 Thread David Roundy
On Fri, Sep 01, 2006 at 11:47:20PM +0100, Duncan Coutts wrote: > On Fri, 2006-09-01 at 17:36 -0400, Robert Dockins wrote: > > Well, AFAIK, the behavior is officially undefined, which is my > > real beef. I agree that it _should_ throw an exception. > > Ah, I had thought it was defined to simply t

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Donn Cave
Quoth Julien Oster <[EMAIL PROTECTED]>: ... | But what happens when two processes use the same file and one process is | writing into it using lazy IO which didn't happen yet? The other process | wouldn't see its changes yet. That's actually a much more general problem, one that I imagine applies

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Julien Oster
Duncan Coutts wrote: Hi, > In practise I expect that most programs that deal with file IO strictly > do not handle the file disappearing under them very well either. At best > the probably throw an exception and let something else clean up. And at least in Unix world, they just don't disappear.

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Duncan Coutts
On Fri, 2006-09-01 at 17:36 -0400, Robert Dockins wrote: > Perhaps I should be more clear. When I said "advanced" above I meant "any > use > whereby you treat a file as random access, read/write storage, or do any kind > of directory manipulation (including deleting and or renaming files)". L

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Robert Dockins
On Friday 01 September 2006 18:01, Donn Cave wrote: > On Fri, 1 Sep 2006, Robert Dockins wrote: > > On Friday 01 September 2006 16:46, Duncan Coutts wrote: > > ... > > >> Note also, that with lazy IO we can write really short programs that are > >> blindingly quick. Lazy IO allows us to save a copy

Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Donn Cave
On Fri, 1 Sep 2006, Robert Dockins wrote: > On Friday 01 September 2006 16:46, Duncan Coutts wrote: ... >> Note also, that with lazy IO we can write really short programs that are >> blindingly quick. Lazy IO allows us to save a copy through the Handle >> buffer. (Never understood why some people

  1   2   >