[Haskell] Re: concurrent haskell, higher-order types and parameterizing by typeclass

oleg at pobox.com oleg at pobox.com
Tue Apr 13 22:22:33 EDT 2004


> data Showable = forall a. Show a => Showable a
>
> writer :: Chan Showable -> IO ()
> writer ch = mapM_ (writeChan ch) [Showable 42, Showable pi, Showable
> "hello", Showable 'c']
>
> printer :: Chan Showable -> IO ()
> printer ch = getChanContents ch >>= mapM_ (\(Showable a) -> print a)
>
> However, this solution requires a new wrapper datatype (or at least a
> new constructor) to be defined for every typeclass to be used in
> Chan-based communication; furthermore, all of the datatypes will be
> identical except for the name of the typeclass.  It seems like I
> should be able to create a type that's parameterized by typeclass,
> i.e. something like:
> data Wrapper c = forall a. c a => Wrapper a
> writer :: Chan (Wrapper Show) -> IO ()

We can do the following:

> {-# OPTIONS -fglasgow-exts #-}
>
> import Data.IORef
>
> data W r = forall a. W a (a->r)
>
> -- emulate the channel
> type Chan a = IORef [W a]
>
> writeChan ch x = do
>         c <- readIORef ch
> 	writeIORef ch (x:c)
>
> getChanContents ch = readIORef ch
>
> -- Channel is parameterized by the answer type!
> writer :: Chan String -> IO ()                                 
> writer ch = mapM_ (writeChan ch) 
>    [W 42 show, W pi show, W "hello" show, W 'c' show]
>                                                                              
> printer :: Chan String -> IO ()                                             
> printer ch = getChanContents ch >>= mapM_ (\(W a h) -> putStrLn $ h a)
>
> main = do 
>         ch <- newIORef []
> 	writer ch
> 	printer ch

That is, pack the handler along with the data. The channel is
parameterized by the answer type of the handler. Indeed, class Show
means that we can apply the function 'show' to any value of the type
in that class -- and get a string. If we use the Showable wrapper as
in the original code, applying show is _the only thing_ we can do with
that value. As we're interested in the answer type anyway (because
there is nothing else we can do with the value), we can parameterize the class
by the answer type. If we can perform several operations on the value,
we can parameterize the channel by a tuple of all answer types.

A cynic might remark that all this exercise with existentials is for
nothing: Indeed, "W x show" is precisely equivalent to just "show x".
Because of the non-strictedness, we can apply (or partially apply) all the
handlers to the value in question and pass these applications through
the channel. Only the needed ones would be evaluated.





More information about the Haskell mailing list