On 06-Oct-1999, Andreas Rossberg <[EMAIL PROTECTED]> wrote:
> Down casts could be done. This would mean that each existential
> constructor had to carry dynamic type information and there would be a
> special pattern matching construct that checks this.
At first I thought a special language construct would be required.
But I realized the other day that special syntax is not essential --
it could be done using only a special library function.
So here's a concrete and very concise proposal for an extension
to Hugs/ghc. I would propose it as an extension to Haskell,
but it relies on the `Typeable' type class and on existential types,
which in Hugs/ghc but which are not part of Haskell 98.
===============================================================================
Proposal: add a function called say `class_cast' to the standard
library, whose type is given by
class_cast :: Typeable t1 => Typeable t2 => t1 -> Maybe t2
and whose semantics are as follows: if `t2' is a type with one
constructor C that takes one argument, and `t1' is a valid type for the
argument of that constructor, then `(class_cast (x::t1)) :: Maybe t2'
returns `Just (C x)', otherwise it returns `Nothing'.
===============================================================================
Here's an example of how it would be used.
class Foo t where
foo_method :: Int
-- the compiler ought to do this instance declaration automatically
instance Typeable Foo where ...
-- the compiler ought to do this type definition automatically too
data AnyFoo = forall t. Foo t => mkFoo t
bar :: Typeable t => t -> Int
bar x = case class_cast x of
Just (mkFoo x_as_foo) -> foo_method x_as_foo
Nothing -> 42
In theory, for any given program, once you know all the types and instance
declarations in the program, you could write a definition of `class_cast'
in Haskell (presuming Dynamic is extended to allow type casts to polymorphic
types, as is possible in Mercury -- this is a very simple extension which
I may describe in more detail in another message). However, in
practice doing so would be pretty infeasible/unmaintainable.
So the idea is that the implementation would provide a definition
for `class_cast' automatically as part of the standard library, with
that definition probably making use of automatically-generated RTTI
of some kind.
Personally I think the syntax above is fine, but if more light-weight
syntax is desired, you could add syntactic sugar.
So, that's it. Any comments?
Feedback on this proposal would be appreciated.
--
Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.