[Haskell-cafe] Making MVar and Chan Instances of Typeable

Benjamin Franksen benjamin.franksen at bessy.de
Fri Nov 5 09:07:43 EST 2004


On Friday 05 November 2004 13:57, Benjamin Franksen wrote:
> Hello Experts,
>
> I need MVar and Chan to be instances of Typeable. Any hint on how this is
> most easily done would be greatly appreciated. I could change the libraries
> and add 'deriving Typeable' but I hesitate to do so.

Ok, I found a solution but it is horrible!

module Helpers where

import Control.Concurrent
import Data.Typeable
import Foreign

instance Typeable a => Typeable (MVar a) where
  typeOf x =
    mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf y]
    where
      y = unsafePerformIO $ do
        z <- newEmptyMVar >>= readMVar
        return (z `asTypeOf` x)

I dearly hope this can be done in a less convoluted fashion.

Ben


More information about the Haskell-Cafe mailing list