pattern-matching extension?

Derek Elkins ddarius at hotpop.com
Fri Dec 5 14:10:35 EST 2003


On Wed, 03 Dec 2003 15:10:07 -0500
"Abraham Egnor" <aegnor at antioch-college.edu> 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?

Dynamics let you do this to some extent and using pattern guards gives
you a reasonable syntax for it.  Clean has syntax like the above for
handling Dynamics and it also supports polymorphic values if I'm not
mistaken.  Dynamics in Haskell as currently implemented are only
monomorphic.  What you could do today is the following... (untested)

{-# OPTIONS -fglasgow-exts #-}
-- you should be able to get something similar in both Hugs and NHC

import Data.Dynamic

-- extension: local existentials (I think NHC only has local universals
-- you can use those to get existentials though.)
data Showable = forall a. Show a => Showable a

instance Show Showable where
    show (Showable showable) = show showable

-- extension: pattern guards (I think Hugs has them but I don't think
-- NHC does. They are only used for prettiness here.)
f :: Dynamic -> String
f val | Just (a :: Int) <- fromDynamic val
            = "got an int, incremented: "++show (a+1)
      | Just (a :: Showable) <- fromDynamic val
            = "got a showable: "++show a
      | otherwise = "got something else"

There are other things you could do, but this seems closest to what you
are looking for.



More information about the Haskell mailing list