On 14-Feb-1999, Joergen Froejk Kjaersgaard <[EMAIL PROTECTED]> wrote:
> Dear Colleges.
>
> Quite a few proposals for Haskell 2 have been posted on this list. I
> think, however, that before we dwell into great detail with the next
> generation of our language, we need to define our goals clearly. What do
> we want to archive with Haskell 2?
IMHO: we should aim to make the language more expressive,
while preserving the essential characteristics of Haskell.
> Haskell 98 has most of the programming features you need. The only
> serious lack I can see is a generic error handling/exception mechanism
> to recover from e.g. division by zero.
I think there's lots of other things lacking too, including the ability
to do destructive update (as with the Hugs/ghc ST module, for example),
optional dynamic typing, existential types, unsafePerformIO, a portable
foreign language interface, etc.
> Where most focus needs to be, I
> believe, is on extension, packing and re-use. Haskell has great features
> to add functionality to existing data types: you simply make the type an
> instance of a class and define the specific functions. On the other
> hand, it's not possible to extend the data type itself. If you have a
> module that defines, say, a "data" type:
>
> data Foo = Bar | Fubar
>
> there is no way to extend this type in another module.
>
> There are two quite different ways out of this. Either we make data
> types extendible or we introduce dynamic binding of functions. What I
> would propose is to make it possible to use classes and types like this:
>
> class Foo a =
> f :: a -> Int
> g :: a -> ...
>
> instance Foo Int where
> f a = a
>
> instance Foo Real where
> f = IntFromReal
>
> h :: [Foo] -> [Int]
> h elems = map f elems
>
> h [1, 2.0] == [1,2]
>
> In Haskell 98 [Foo] makes no sense. I want [Foo] to mean a list of
> elements of types of class Foo. When a list is built, each element is
> augmented with pointers to the functions defined in class Foo for its
> concrete type. The only operations allowed on elements in a list of
> [Foo] are the operation defined in class [Foo].
>
> This is as good, if not better, as having extendible "data" types. You
> can extend a class by adding new instances exactly as in Haskell 98 but
> classes become much more useful. Their meaning become very close to that
> of virtual classes with no data members in C++.
Existential types will give you most of the benefits of this with
fewer drawbacks. E.g.
data AnyFoo = Foo t => MkAnyFoo t
instance Foo AnyFoo where
f (MkAnyFoo x) = f x
g (MkAnyFoo x) = g x
h :: [AnyFoo] -> [Int]
h elems = map f elems
h [MkAnyFoo 1, MkAnyFoo 1.0] == [1,2]
--
Fergus Henderson <[EMAIL PROTECTED]> | "Binaries may die
WWW: <http://www.cs.mu.oz.au/~fjh> | but source code lives forever"
PGP: finger [EMAIL PROTECTED] | -- leaked Microsoft memo.