Re: [Haskell-cafe] Expressing seq

2006-09-28 Thread Janis Voigtlaender

Chad Scherrer wrote:


 There must be a subtlety I'm missing, right?

What if the types are not instances of Eq?

Jason



Thanks, I figured it was something simple. Now I just to convince
myself there's no way around that. Is there a proof around somewhere?


Yes, there is a proof that

  seq :: a - b - b

with the semantics as described in the Haskell report cannot be defined
in Haskell minus seq. It goes as follows:

If seq were so definable, then it would have to fulfill the free theorem
derived from its type in Haskell minus seq (read: System F plus fix).
But it doesn't. See Section 5 of

  http://wwwtcs.inf.tu-dresden.de/~voigt/seqFinal.pdf

Ciao, Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Expressing seq

2006-09-27 Thread Chad Scherrer

I was reading on p. 29 of A History of Haskell (a great read, by the
way) about the controversy of adding seq to the language. But other
than for efficiency reasons, is there really any new primitive that
needs to be added to support this?

As long as the compiler doesn't optimize it away, why not just do
something like this (in ghci)?

Prelude let sq x y = if x == x then y else y
Prelude 1 `sq` 2
2
Prelude (length [1..]) `sq` 2
Interrupted.

There must be a subtlety I'm missing, right?
--

Chad Scherrer

Time flies like an arrow; fruit flies like a banana -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Jason Dagit

On 9/27/06, Chad Scherrer [EMAIL PROTECTED] wrote:

I was reading on p. 29 of A History of Haskell (a great read, by the
way) about the controversy of adding seq to the language. But other
than for efficiency reasons, is there really any new primitive that
needs to be added to support this?

As long as the compiler doesn't optimize it away, why not just do
something like this (in ghci)?

Prelude let sq x y = if x == x then y else y
Prelude 1 `sq` 2
2
Prelude (length [1..]) `sq` 2
Interrupted.

There must be a subtlety I'm missing, right?


What if the types are not instances of Eq?

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Chad Scherrer


 There must be a subtlety I'm missing, right?

What if the types are not instances of Eq?

Jason



Thanks, I figured it was something simple. Now I just to convince
myself there's no way around that. Is there a proof around somewhere?
--

Chad Scherrer

Time flies like an arrow; fruit flies like a banana -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Chris Kuklewicz
Chad Scherrer wrote:
 I was reading on p. 29 of A History of Haskell (a great read, by the
 way) about the controversy of adding seq to the language. But other
 than for efficiency reasons, is there really any new primitive that
 needs to be added to support this?
 
 As long as the compiler doesn't optimize it away, why not just do
 something like this (in ghci)?
 
 Prelude let sq x y = if x == x then y else y
 Prelude 1 `sq` 2
 2
 Prelude (length [1..]) `sq` 2
 Interrupted.
 
 There must be a subtlety I'm missing, right?

The (sq x) function depends on x being an instance of typeclass Eq.

Imagine a new typeclass Seq that is auto-defined for all types:

class Seq a where
  seq :: a - (b - b)

data Foo x = Bar x | Baz | Foo y x

The instances always use a case to force just enough evaluation to compute the
constructor, then return id:

instance Seq Foo where
  seq a = case a of
   Bar _   - id
   Baz - id
   Foo _ _ - id

foo1,foo2 :: Foo Int
foo1 = undefined
foo2 = Bar 1

Now (seq foo1) b will also be undefined which (seq foo2) b will be id b
which is b.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Expressing seq

2006-09-27 Thread Bertram Felgenhauer
Chad Scherrer wrote:
 Prelude let sq x y = if x == x then y else y
 Prelude 1 `sq` 2
 2
 Prelude (length [1..]) `sq` 2
 Interrupted.

 There must be a subtlety I'm missing, right?

Two, at least:

First, your sq has a different type, as it requires an Eq instance:

Prelude :t sq
sq :: (Eq a) = a - t - t
Prelude :t seq
seq :: a - b - b

Secondly, your sq is more akin to a deepSeq in that it forces all of
its value instead of just evaluating to weak head normal form.

Prelude [undefined] `seq` 1
1
Prelude [undefined] `sq` 1
*** Exception: Prelude.undefined

You could implement seq explicitely for many types, for example,

  seqList []x = x
  seqList (_:_) x = x

but not for function types.

HTH,

Bertram
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe