Unexpected Typeable behaviour; Prelude.undefined

L.S., I'm currently writing code where I want some ADTs to be parametric with a monad. There are some extra conditions that I place on my parameter, but I've boiled things down to minimal reproducibility. When I define MyADT as follows: import Data.Typeable data MyADT m = MyADT (m ()) instance (Typeable1 m, Monad m) => Typeable (MyADT m) where typeOf t@(MyADT _) = mkTyCon "MyADT" `mkTyConApp` [typeOf1 ((return :: Monad m => MyADT m -> m (MyADT m)) t)] it compiles fine and GHCi works as expected on a single instance of MyADT: *Main> typeOf (MyADT (return () :: IO ())) MyADT IO However, as soon as I place my data type in a structure of sorts, things break down: *Main> typeOf [(MyADT (return () :: IO ()))] *** Exception: Prelude.undefined *Main> typeOf (Just (MyADT (return () :: IO ()))) *** Exception: Prelude.undefined *Main> typeOf ((return :: a -> IO a) (MyADT (return () :: IO ()))) *** Exception: Prelude.undefined But if I stick a number in a similar structure, typeOf works just fine: *Main> typeOf ((return :: a -> IO a) 5) IO Integer I don't quite understand where the undefined comes from. I'm certainly not using it anywhere (as shown by the minimal reproduction above). Weirder still, when I *do* introduce a nice error, that too does not come up, viz. import Data.Typeable data MyADT m = MyADT (m ()) instance (Typeable1 m, Monad m) => Typeable (MyADT m) where typeOf t@(MyADT _) = error "foobar" with GHCi-session: *Main> typeOf (MyADT (return () :: IO ())) *** Exception: foobar *Main> typeOf ((return :: a -> IO a) (MyADT (return () :: IO ()))) *** Exception: Prelude.undefined *Main> typeOf $ Just (MyADT (return () :: IO ())) *** Exception: Prelude.undefined *Main> typeOf $ Just 42 Maybe Integer FYI, I'm using GHC 7.0.3, as installed with the Haskell Platform 2011.2.0.1. Am I overlooking something? Any help would be appreciated. Regards, Philip

Hi Philip,
On 28 August 2011 23:44, Philip Holzenspies
import Data.Typeable
data MyADT m = MyADT (m ())
instance (Typeable1 m, Monad m) => Typeable (MyADT m) where typeOf t@(MyADT _) = mkTyCon "MyADT" `mkTyConApp` [typeOf1 ((return :: Monad m => MyADT m -> m (MyADT m)) t)]
IIRC, typeOf is supposed to work with undefined as the argument. Try: typeOf (undefined :: Int) See: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Typeab... I think the undefined is merely because the pattern matching you use in the instance declaration fails. Hope this helps, Ozgur

On Sun, Aug 28, 2011 at 18:44, Philip Holzenspies
instance (Typeable1 m, Monad m) => Typeable (MyADT m) where typeOf t@(MyADT _)
typeOf is usually invoked with an undefined parameter; it should use types, never values. Here you've defined it to deconstruct what it's passed, which means that anything that uses it in the usual way (`typeOf (undefined :: someType)') will immediately throw undefined. You don't need a deconstructor there; you (correctly) throw away the value, and it doesn't provide any type information not already available from the instance declaration. `typeOf t' should be good enough. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Dear Brandon, Ozgur, et al,
Thanks very much for you explanation. This seems to be a perfectly reasonable explanation; the wrapper-types I used probably explicitly invoke typeOf with undefined. The problem here, however, is that in my actual program, I don't use ADTs, but I use GADTs, so as to carry the context (Monad, Typeable1) with the constructor. To get to this context, I must pattern-match with the constructor. It seems hiding contexts (which I really like about GADTs) isn't "available" consistently. Oh well ;)
Regards,
Philip
On 29 Aug 2011, at 01:20, Brandon Allbery wrote:
On Sun, Aug 28, 2011 at 18:44, Philip Holzenspies

The problem with hiding the context in the constructor is that there's no
guarantee that the context actually exists in the first place; for example,
given this type
data IsInt a where
Proof :: IsInt Int
this is a legal program:
foo :: IsInt Bool
foo = undefined
That said, you are still just fine to hide the context in the constructor at
the call site:
data MyGADT m where
MonadAction :: (Typeable1 m, Monad m) -> m () -> MyGADT m
instance (Typeable1 m, Monad m) => Typeable (MyGADT m) where
typeof t = ...
getTypeRep :: MyGADT m -> TypeRep
getTypeRep x@(MonadAction _) = typeof (undefined `asTypeOf` x)
Here we unpack the context from x and use it to construct the 'typeof'
function for MyGADT m.
-- ryan
On Mon, Aug 29, 2011 at 2:06 AM, Philip Holzenspies
Dear Brandon, Ozgur, et al,
Thanks very much for you explanation. This seems to be a perfectly reasonable explanation; the wrapper-types I used probably explicitly invoke typeOf with undefined. The problem here, however, is that in my actual program, I don't use ADTs, but I use GADTs, so as to carry the context (Monad, Typeable1) with the constructor. To get to this context, I must pattern-match with the constructor. It seems hiding contexts (which I really like about GADTs) isn't "available" consistently. Oh well ;)
Regards, Philip
On 29 Aug 2011, at 01:20, Brandon Allbery wrote:
On Sun, Aug 28, 2011 at 18:44, Philip Holzenspies
wrote: instance (Typeable1 m, Monad m) => Typeable (MyADT m) where typeOf t@(MyADT _)
typeOf is usually invoked with an undefined parameter; it should use types, never values. Here you've defined it to deconstruct what it's passed, which means that anything that uses it in the usual way (`typeOf (undefined :: someType)') will immediately throw undefined.
You don't need a deconstructor there; you (correctly) throw away the value, and it doesn't provide any type information not already available from the instance declaration. `typeOf t' should be good enough.
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Brandon Allbery
-
Ozgur Akgun
-
Philip Holzenspies
-
Ryan Ingram