simulating dynamic dispatch

oleg@pobox.com oleg@pobox.com
Sun, 23 Mar 2003 13:41:48 -0800 (PST)


Hal Daume wrote:
> -- *Main> test $ MkFoo (0::Int)
> -- Just True
> -- *Main> test $ MkBar 'a'      
> -- Just True

> i forgot to mention the constraint
> that i don't want the user to have to use the MkFoo/MkBar
> constructors.  if i could use them internally to 'test', that would be
> great, but that's what i couldn't get to work :).

It can be done without burdening the user with typing MkFoo and
MkBar. In fact, the enclosed code shows that it is possible to
implement the dynamic dispatch on a type class context -- exactly the
way you wanted it, it seems. The code resorts to no unsafe operations.

Here's the test:

-- *Main> test (1::Int)
-- "this is foo calling: 1"
-- *Main> test 'a'
-- "this is bar calling: 'a'"
-- *Main> test [True,False]
-- "this is quu calling: [True,False]"

Here's the code

-- Dynamic dispatch on a constraint: Foo, Bar, or Quux

-- The constraints to dispatch on

class Foo a where { foo :: a -> String }
class Bar a where { bar :: a -> String }
class Quu a where { quu :: a -> String }

-- Populate the type classes
instance Foo Int where
    foo x = "this is foo calling: " ++ (show x)
    
instance Bar Char where
    bar x = "this is bar calling: " ++ (show x)
    
instance Quu [Bool] where
    quu x = "this is quu calling: " ++ (show x)


-- The Universe (with hidden constraints)
data PACK = forall a . Foo a => MkFoo a | forall a . Bar a => MkBar a
            | forall a . Quu a => MkQuu a

-- The packer
class Packable a where
    pack:: a -> PACK

-- The following three instances seem to be the "inverse"
-- of the "instance Foo Int" .. instance Quu [Bool]
-- The three instances below do an important job: they "introduce"
-- the class context, so to speak.
-- Also, a type can be a member of several type classes. The following
-- instances resolve the ambiguity. For example, even if Int were a member
-- of a class Bar (in addition to being the member of a class Foo), the first
-- instance declaration below resolves Int to a class Foo (and so we would
-- dispatch on Foo when we see an Int).

instance Packable Int where
    pack = MkFoo
    
instance Packable Char where
    pack = MkBar
    
instance Packable [Bool] where
    pack = MkQuu

-- The dispatcher
instance Foo PACK where
    foo (MkFoo x) = foo x

instance Bar PACK where
    bar (MkBar x) = bar x

instance Quu PACK where
    quu (MkQuu x) = quu x
    

test:: (Packable a) => a -> String
test = dispatch . pack
  where
    dispatch x = case x of
          (MkFoo a) -> foo a
          (MkBar a) -> bar a
          (MkQuu a) -> quu a

-- *Main> test (1::Int)
-- "this is foo calling: 1"
-- *Main> test 'a'
-- "this is bar calling: 'a'"
-- *Main> test [True,False]
-- "this is quu calling: [True,False]"