On 08-Jan-2003, Andrew J Bromage <[EMAIL PROTECTED]> wrote:
> On Wed, Jan 08, 2003 at 08:42:20AM +1100, Thomas Conway wrote:
>
> > Mercury has a type "univ" which might be declared something like:
>
> data Univ = forall a. Univ a
>
> > I believe (nth hand) that something similar has been d
Dear Haskell list member,
It is with regret that I must inform you of the death of Tony Davie,
who passed away on Wednesday, January 9th following a long-standing
battle with leukemia. Many of you who came into contact with him will
have been impressed by his in-depth understanding of his subject
A few things.
If you give newFilterIS a type signature it works fine. Note that this
requires a higher-rank type, but that's okay:
> data FilterIS = FilterIS { source :: InputStream s => s, filter
>:: Filter }
> newFilterIS :: (forall s . InputStream s => s) -> Filter -> FilterIS
> newFilt
Simon Marlow wrote:
> The original version should also evaluate the expression 'cis wn' only
> once: [...]
Nice theory, but GHC's interpreter and compiler behave differently:
-- Main.hs ---
module Main where
import Data.Complex ( Complex )
There once lived a Tony named Davie,
whose favourite language was lazy.
He worked with persistence,
and humorous insistence
on limericks driving you crazy.
Sorry I never came up with one when you asked us to.
Claus
- Original Message -
From: "Kevin Hammond" <[EMAIL P
Fergus Henderson wrote:
> > Maybe in Haskell 2.
>
> Yes, it would be nice to have a built-in, type-safe, version of Dynamic
> in Haskell 2.
It would also be nice if it were a little less abstract; e.g. either
exposing the constructors for Dynamic and TypeRep or providing
suitable accessors woul
G'day all.
On Tue, Jan 14, 2003 at 07:13:57PM +1100, Fergus Henderson wrote:
> That's not the only problem. The other problem is that because
> `Typeable' instances aren't built-in, `fromDynamic' is not type-safe.
> The implementation of `fromDynamic' calls `typeOf' and then if the types
> match
"Marc Ziegert" <[EMAIL PROTECTED]> writes:
> It would be nice to be able to overload class-functions like
>classes:
>
> instance (+), (-) -> Vector where
> (+) v1 v2 = ...
> (-) v1 v2 = ...
>
> instead of overloading parts of a class... (because o
Hi all,
There is a rather small section on the Haskell web page dedicated to
Haskell in industry, but my guess is that it's both somewhat outdated and
somewhat incomplete. I'm hoping to be able to scavenge a bit more
information off this list.
Basically, I'm looking into the possibility of findi
Glynn Clements <[EMAIL PROTECTED]> wrote,
> Fergus Henderson wrote:
>
> > > Maybe in Haskell 2.
> >
> > Yes, it would be nice to have a built-in, type-safe, version of Dynamic
> > in Haskell 2.
>
> It would also be nice if it were a little less abstract; e.g. either
> exposing the constructors
10 matches
Mail list logo