As Bernie and Derek already pointed out, in principle, the rich work on
intensional polymorphism and dynamic typing comes to mind. In
particular, dynamics are readily supported in Haskell.

Let me add the following.

Type-safe cast is now clearly localised in the module Data.Typeable.
(Due to a refactoring from last summer, which will be effective in GHC 6.2)

Here I recall the type of type-safe cast as used in "scrap your boilerplate":

cast :: (Typeable a, Typeable b) => a -> Maybe b

No detouring to Dynamics needed.
Having *type-safe cast* means that you can also perform *type case*.

So here we go.

import Data.Typeable

We now define a function along the lines of what you asked for.
(I will discuss below the limitations of this.)

f :: (Show a, Typeable a) => a -> String
f a = (maybe (maybe others
float (cast a) )
int (cast a) )
where
-- do something with ints
int :: Int -> String
int a = "got an int, incremented: " ++ show (a + 1)
-- do something with floats
float :: Float -> String
float a = "got a float, multiplied by .42: " ++ show (a * 0.42)
-- do something with all other typeables
others = "got something else: " ++ show a


Full examples and relevant Data.* modules at
http://www.cs.vu.nl/boilerplate/#suite
(see "Type-case demo")



Discussion:


--------------------------------------------------------------------------

- So type case works fine. I agree with you that having syntax for
 type case  (instead of folding over maybies as I do above) would be great.

--------------------------------------------------------------------------

- Your example asks for more. It asks for what I would call
"type-class case". You want to cast values whose
type possibly instantiates this or that class, for example, the Show class.


  I agree that this would be cool to have. Especially when programming
  with generics, one sometimes wants to do what you just demonstrated:
  show things.

  It is not clear to me how many users such a language
  extension would have however. It is a major extension. Just look at
  the type of your "f". It pretends to be parametrically polymorphic.
  So an argument would not carry any class dictionaries. When doing
  the type-class case, these dictionaries had to be "invented". Nice
  research topic!!!

--------------------------------------------------------------------------

- Your particular syntax is problematic in two respects.

1.
The type of "f" looks too innocent. There is some preference (not a dogma)
in Haskell that unconstrained type variables stand for parametric polymorphism.


 2.
 One would maybe want to use another symbol than "::" because otherwise
 one could get accidentally well-typed patterns.

--------------------------------------------------------------------------

- The specific "type-class case" for Show is of course not necessary if
 all relevant values are known to be showable. So we can go for the Data
 rather than the Typeable class. Then my example becomes as follows:

f :: Data a => a -> String
f a = -- as before
where

 -- do something with all other data
 -- NOTE the gshow as opposed to show
 others = "got something else: " ++ gshow a


Ralf


Abraham Egnor wrote:

I've occasionally wanted some sort of equivalent of an instanceOf function
in haskell, i.e. one that would let me define a function that could
dispatch on the type of its argument as well as the value.  One option
I've seen for this is
"http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
unfortunately has the downside of requiring you to write both a
constructor for PACK and an instance of Packable for each type you'd like
to dispatch on.

The thought occurred to me that it is (intuitively) natural to do this via
extending the pattern-matching facility to include types as well as
literal values, i.e. something like:

f :: a -> String
f (a :: Int) = "got an int, incremented: "++(show (a+1))
f (a :: Show q => q) = "got a showable: "++(show a)
f _ = "got something else"

This has a couple of nice features - it's a simple extension of the
syntax, and acts as a sort of type-safe typecast.  However, I have zero
knowledge of how hard it would be to implement this, and there may be
theoretical difficulties I haven't seen.  Thoughts?

Abe

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell




_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to