ANNOUNCE: popenhs-1.00.0 released

2002-01-25 Thread Jens Petersen
Version 1.00.0 of popenhs is out. You can get it from: http://www.01.246.ne.jp/~juhp/haskell/popenhs/ popenhs is a small library providing lazy string output from and input to a subprocess. The interface provided by "popen" now differs from the "popen3" offered in 0.00 by taking an inp

Re: Explicit Universal Quantification Bug?

2002-01-25 Thread Janis Voigtlaender
Rijk-Jan van Haaften wrote: > ... > In the last one, after the type checker has verified > that deTIM is type-correct, it can safely generalize > the type of deTIM, because it is a top-level function. > ... > However, in > > >runTIM t = case t of {TIM l -> runST l} > the argument 't' is non-generi

RE: Explicit Universal Quantification Bug?

2002-01-25 Thread Simon Peyton-Jones
| I'm trying to learn more about Explicit Universal | Quantification so I decide to run the following supposedly | correct code from the ghc user | guide: | | >module Dummy where | > | >import ST | > | >newtype TIM s a = TIM (ST s (Maybe a)) | > | >runTIM :: (forall s. TIM s a) -> Maybe a | >ru

RE: Explicit Universal Quantification Bug?

2002-01-25 Thread John Hughes
| I'm trying to learn more about Explicit Universal | Quantification so I decide to run the following supposedly | correct code from the ghc user | guide: | | >module Dummy where | > | >import ST | > | >newtype TIM s a = TIM (ST s (Maybe a)) | > |

Re: ideas for compiler project

2002-01-25 Thread Jerzy Karczmarczuk
Simon Peyton-Jones: > Lots of people have observed that Haskell might be a good "scripting > language" for numerical computation. In complicated numerical > applications, the program may spend most of its time in (say) matrix > multiply, which constitutes a tiny fraction of the code for the > a

Re: (no subject)

2002-01-25 Thread John Hughes
> Those two constructs are not the same > Compare > newtype T1 = C1 Bool > dataT2 = C2 !Bool As for as I can tell, the only difference in the Report between a newtype and a tuple type with a completely strict constructor is in the

Re: newtype pattern matching

2002-01-25 Thread Marcin 'Qrczak' Kowalczyk
25 Jan 2002 08:00:24 +0100, Martin Norbäck <[EMAIL PROTECTED]> pisze: > newtype T1 = C1 Bool > dataT2 = C2 !Bool > > the difference is that the constructor C1 does not exist, so only the > following values exist for T1: > > C1 True (which is the represented as True) > C1 False (which is th

type specs not making it in to functions

2002-01-25 Thread Hal Daume III
consider the following definition: > class C a where foo :: a -> Int > instance C Bool where foo _ = 5 I can then say: > bar :: C a => a -> Int > bar (x :: a) = foo (undefined :: a) But not: > bar :: C a => a -> Int > bar x = foo (undefined :: a) because it tries to use a new scope for the t

Re: newtype pattern matching

2002-01-25 Thread David Feuer
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] said: The side effect of using data with a strict argument instead of newtype is that f' (C2 x) (C2 y) = C2 (f x y) unexpectedly becomes strict in both arguments, and we would have to write f' x y = C2 (f (case x of C2 x' -> x')

Re: type specs not making it in to functions

2002-01-25 Thread Ashley Yakeley
At 2002-01-25 14:00, Hal Daume III wrote: >> class D a where constMember :: Int >> instance D Int where constMember = 8 > >It seems ehre that there's no way to extract constMember for a >/particular/ class, since you can't tell it what "a" is supposed to >be. So, instead, I do: > >> class D a wh

Announce: School of Expression software

2002-01-25 Thread Sigbjorn Finne
A Windows installer packaging up the supporting software to Paul Hudak's "School of Expression" book in one convenient bundle is now available via the Hugs98 downloads page (see http://haskell.org/hugs ). A tar-bundle is provided for other platforms also. It includes the source code + supporting

Re: newtype pattern matching

2002-01-25 Thread Jan-Willem Maessen
I think one crucial point is being lost in the ongoing discussion of pattern-matching and newtype: newtype is supposed permit *erasure* of construction and pattern matching. There is *no runtime cost* because the type disappears at compile time. Even a non-optimising Haskell implementatio