[Haskell-cafe] why typeRepArgs (typeOf "hello") is [Char] ?
Ross Mellgren
rmm-haskell at z.odi.ac
Mon Feb 2 15:38:58 EST 2009
Sure:
(+) :: Integer -> Integer -> Integer (really Num a => a -> a ->
a, but we'll use the defaulted one)
Which is really
(+) :: -> Integer (-> Integer Integer) (that is, the function type
constructor is * -> * -> * and right associative)
So when you say typeRepArgs (typeOf (+)) you get Integer and (->
Integer Integer), which pretty-prints as (Integer -> Integer)
It is possible, but you have to check if the type constructor is
really a function type, e.g.:
import Data.Typeable
funTyCon :: TyCon
funTyCon = mkTyCon "->"
argsOf :: TypeRep -> [TypeRep]
argsOf ty
| typeRepTyCon ty == funTyCon = let (x:y:[]) = typeRepArgs ty in
x : argsOf y
| otherwise = []
*Main Data.Typeable> let f = (undefined :: Int -> Char -> String -> ())
*Main Data.Typeable> argsOf (typeOf f)
[Int,Char,[Char]]
-Ross
On Feb 2, 2009, at 3:27 PM, minh thu wrote:
> Thanks. Could you add to your explanation this one :
>
> *Graph> typeRepArgs (typeOf (+))
> [Integer,Integer -> Integer]
>
> In fact, I tried to write a function that would give the types used by
> a function,
> for instance [Integer, Integer, Integer] for (+) (the last one would
> be the 'return' type).
> So I applied recursively typeRepArgs to the second element of the list
> (if any) (here, Integer -> Integer).
>
> It worked well until I tried it on a function like :: Char -> Int ->
> [Char] where
> the last recursive call gives [Char] instead of [].
>
> Is it possible to write such a function ?
>
> Thank you,
> Thu
>
>
> 2009/2/2 Ross Mellgren <rmm-haskell at z.odi.ac>:
>> The type of "hello" is String, which is [Char], which is really []
>> Char
>> (that is, the list type of kind * -> *, applied to Char).
>>
>> 1, 'a', and True are all simple types (I'm sure there's a more
>> particular
>> term, maybe "monomorphic"?) with no type arguments.
>>
>> [] has a type argument, Char.
>>
>> Consider:
>>
>> Prelude Data.Typeable> typeRepArgs (typeOf (Just 1))
>> [Integer]
>>
>> and
>>
>> Prelude Data.Typeable> typeRepArgs (typeOf (Left 'a' :: Either Char
>> Int))
>> [Char,Int]
>>
>> -- typeRepArgs is giving you the arguments of the root type
>> application, []
>> (list) in your case, Maybe and Either for the two examples I gave.
>>
>> Does this make sense?
>>
>> -Ross
>>
>> On Feb 2, 2009, at 3:09 PM, minh thu wrote:
>>
>>> Hello,
>>>
>>> With Data.Typeable :
>>>
>>> *Graph> typeRepArgs (typeOf 1)
>>> []
>>> *Graph> typeRepArgs (typeOf 'a')
>>> []
>>> *Graph> typeRepArgs (typeOf True)
>>> []
>>> *Graph> typeRepArgs (typeOf "hello")
>>> [Char]
>>>
>>> I don't understand why the latter is not []. Could someone explain
>>> it ?
>>>
>>> Thank you,
>>> Thu
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
More information about the Haskell-Cafe
mailing list