why typeRepArgs (typeOf "hello") is [Char] ?

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

On Mon, 2009-02-02 at 21:09 +0100, 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 ?
Because ("hello" :: [] Char)? Prelude> :t "hello" "hello" :: [Char] jcc

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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
: 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks a lot !
2009/2/2 Ross Mellgren
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
: 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2009 Feb 2, at 15:27, minh thu wrote:
Thanks. Could you add to your explanation this one :
*Graph> typeRepArgs (typeOf (+)) [Integer,Integer -> Integer]
The actual representation of an n-argument function in Haskell is a single-argument function that returns an (n-1)-argument function. (Technically, Haskell function applications are uncurried.) This is reflected in typing by (->) being right associative:
(+) :: Num a => a -> a -> a :: Num a => a -> (a -> a)
the former being how we usually think about it and the latter being how Haskell actually sees it. The typeRepArgs of (+) are set by this and by defaulting due to the monomorphism restriction to give you [Integer,Integer -> Integer] which corresponds to
(+) :: Integer -> (Integer -> Integer) :: Integer -> Integer -> Integer
which is the previous definition, swapping the internal and external forms and filling in Integer for (Num a =>) a via defaulting.
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 [].
To get information about higher-kinded types, you want typeRepTyCon:
Prelude Data.Typeable> typeRepTyCon (typeOf (+)) ->
which is how you should determine that you want to deconstruct a function type. Or for the final argument in your case:
Prelude Data.Typeable> typeRepTyCon (typeOf "foo") []
There's the [] you wanted. typeRepArgs then informs us that the tycon [] is applied to a sing;e type argument:
Prelude Data.Typeable> typeRepArgs (typeOf "foo") [Char]
so the final argument type is ([] Char) (better known as [Char]). The fact that it comes out as [Char] may be confusing you; the length of the list represents the number of type arguments the tycon takes, so you've been given a Char and need typeRepTyCon to get the rest of the story. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
Jonathan Cast
-
minh thu
-
Ross Mellgren