Making MVar and Chan Instances of Typeable

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. Cheers, Ben

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

On Friday 05 November 2004 15:07, Benjamin Franksen wrote:
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)
which is wrong because it also passes the typeOf of the MVar and not the content. This one is correct, I hope: instance Typeable a => Typeable (MVar a) where typeOf x = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf v] where v = unsafePerformIO $ do y <- newEmptyMVar readMVar (y `asTypeOf` x) On Friday 05 November 2004 16:44, Koji Nakahara wrote:
instance Typeable a => Typeable (MVar a) where typeOf (x :: MVar a) = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]
Yes, that's it. The above is a lot more convoluted but has a small advantage: it doesn't need -fglasgow-exts. I understand now, why pattern signatures were deemed a useful feature! Thanks to all who helped. Cheers, Ben

On Fri, Nov 05, 2004 at 01:57:53PM +0100, 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.
The easiest way is to hide type constructor Chan: import Control.Concurrent import Data.Generics newtype MyChan a = MyChan (Chan a) deriving Typeable Of course, you can also write the instance for Chan by hand. Best regards, Tom -- .signature: Too many levels of symbolic links

On Friday 05 November 2004 15:51, you wrote:
On Fri, Nov 05, 2004 at 01:57:53PM +0100, 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.
The easiest way is to hide type constructor Chan:
import Control.Concurrent import Data.Generics
newtype MyChan a = MyChan (Chan a) deriving Typeable
Of course, you can also write the instance for Chan by hand.
This might be the easiest way, but is otherwise inconvenient. I tried to write the instances by hand. My first attempt was: instance Typeable a => Typeable (MVar a) where typeOf x = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)] but unfortunately this doesn't work. Ghc complains about Ambiguous type variable `a1' in the top-level constraint: `Typeable a1' arising from use of `typeOf' at Helpers.hs:8 The reason is apparently that inside the definition of typeOf the type variable 'a' is not unified with the 'a' from the instance header. I could write typeOf (MVar x) = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf y] where y = undefined `asTypeOf` x but the doc says that typeOf should be written without evaluating its argument, so that is ca be passed 'undefined'. What I need is a trick that enables me to get at the type of the 'a' in the instance header for use inside definition of 'typeOf'. Ben

On Fri, 5 Nov 2004 14:43:55 +0100
Benjamin Franksen
the instances by hand. My first attempt was:
instance Typeable a => Typeable (MVar a) where typeOf x = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]
but unfortunately this doesn't work. Ghc complains about
Ambiguous type variable `a1' in the top-level constraint: `Typeable a1' arising from use of `typeOf' at Helpers.hs:8
The reason is apparently that inside the definition of typeOf the type variable 'a' is not unified with the 'a' from the instance header. I could write
You can write: instance Typeable a => Typeable (MVar a) where typeOf (x :: MVar a) = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)] Hope it helps, Koji Nakahara

On Fri, Nov 05, 2004 at 01:57:53PM +0100, 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.
Cheers, Ben
It can be done in Haskell 98 the same way `asTypeOf' is defined in the Report: instance Typeable a => Typeable (MVar a) where typeOf v = mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (t v)] where t :: a b -> b t = undefined Groetjes, Remi -- Nobody can be exactly like me. Even I have trouble doing it.
participants (4)
-
Benjamin Franksen
-
Koji Nakahara
-
Remi Turk
-
Tomasz Zielonka