understanding typeable

i am trying to figure out how typeable works, so i have this data type data Foo = FooC Int deriving (Data, Typeable, Show) So how come this works:
funResultTy (typeOf ((+) 1)) (typeOf 1) Just Integer
but this doesnt:
funResultTy (typeOf FooC) (typeOf 1) Nothing
FooC is of type t -> u and 1 is of type t so the result should be u? I don't think t and u need to be the same since
funResultTy (typeOf (\a -> a:[1])) (typeOf 1) Just [Integer]
works fine. So given a constructor, how come i cant seem to construct a type out of it?

On Sunday 12 April 2009 3:42:35 pm Anatoly Yakovenko wrote:
i am trying to figure out how typeable works, so i have this data type
data Foo = FooC Int deriving (Data, Typeable, Show)
So how come this works:
funResultTy (typeOf ((+) 1)) (typeOf 1)
Just Integer
but this doesnt:
funResultTy (typeOf FooC) (typeOf 1)
Nothing
FooC is of type t -> u and 1 is of type t so the result should be u? I don't think t and u need to be the same since
funResultTy (typeOf (\a -> a:[1])) (typeOf 1)
Just [Integer]
works fine. So given a constructor, how come i cant seem to construct a type out of it?
Judging from the other types, 'typeOf 1' is defaulting to Integer. FooC, per your declaration, has type 'Int -> Foo'. So, you're probably asking it what happens when you apply an Int -> Foo to an Integer, which would be a type error, and explains the Nothing, I think. -- Dan

ah, Int vs Integer, i didn't see that at all. Thats kind of weird, i thought 1 could be either one. This works
funResultTy (typeOf FooC) (typeOf (1::Int)) Just ParseG.Foo
but
funResultTy (typeOf FooC) (typeOf $ fromIntegral 1) Nothing
doesn't so, how do i actually do something with this? is there a way that i can pull out the computation? Like there is a -> TypeRep, is there a TypeRep -> a function? cast doesn't seem to do what i want
let a::Foo = fromJust $ cast $ fromJust $ funResultTy (typeOf FooC) (typeOf (1::Int)) a *** Exception: Maybe.fromJust: Nothing

On Monday 13 April 2009 1:18:40 am Anatoly Yakovenko wrote:
ah, Int vs Integer, i didn't see that at all. Thats kind of weird, i thought 1 could be either one.
It can, but typeOf has to pick one instance to use. The default for Num is Integer, so that's what it chooses without any annotation making it choose otherwise. If there weren't any defaulting rules, you'd just get an error saying that "typeOf 1" is ambiguous, and you'd need to add an annotation to say which instance you want.
This works
funResultTy (typeOf FooC) (typeOf (1::Int))
Yep, this tells it to use Int explicitly.
but
funResultTy (typeOf FooC) (typeOf $ fromIntegral 1)
Nothing
doesn't
fromIntegral 1 is the same as a literal 1, so this is not surprising.
so, how do i actually do something with this? is there a way that i can pull out the computation? Like there is a -> TypeRep, is there a TypeRep -> a function? cast doesn't seem to do what i want
let a::Foo = fromJust $ cast $ fromJust $ funResultTy (typeOf FooC) (typeOf (1::Int)) a
*** Exception: Maybe.fromJust: Nothing
I think you want Dynamics. TypeRep is just that, a value representing a type. There's no value of that type in it. The only reason typeOf takes a value of the given type is to specify what type you want a TypeRep of. So both: typeOf (undefined :: Int) typeOf (1 :: Int) return the same thing, a TypeRep representing Int. A Dynamic, on the other hand, can be looked at as a pair of a value and a TypeRep tag specifying its type, which sounds like what you want. Look at Data.Dynamic. As for your other question, a TyCon is a representation of a type constructor, not a data constructor. FooC and BarC are data constructors. Type constructors are more like Maybe, which take types to types. Although that TyCon type seems to take Foo (which would normally not be considered a type constructor proper, I think) as a type constructor too. Anyhow, both 'FooC 1' and 'BarC 2' have type Foo, so their type is Foo, and the 'constructor' part is Foo, according to the library. However, for instance: typeOf (Just ()) ==> Maybe () typeRepTyCon (typeOf (Just ())) ==> Maybe typeOf (Nothing :: Maybe ()) ==> Maybe () typeRepTyCon (typeOf (Nothing :: Maybe ())) ==> Maybe -- Dan
participants (2)
-
Anatoly Yakovenko
-
Dan Doel