Data.Typeable TypeRep Ord instance.

Why TypeRep does have equality and doesn't have ordering? It would be good to have that. Right now when I have to order two type representations I convert them to string and then compare. This is somewhat inefficient and not quite straightforward.

Why should they? You can compare them in whatever way you like. And there
isn't a natural/inherent sense of total order between types.
On Sun, Dec 5, 2010 at 6:08 AM, Serguey Zefirov
Why TypeRep does have equality and doesn't have ordering?
It would be good to have that.
Right now when I have to order two type representations I convert them to string and then compare. This is somewhat inefficient and not quite straightforward.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tianyi Cui

2010/12/5 Tianyi Cui
Why should they? You can compare them in whatever way you like. And there isn't a natural/inherent sense of total order between types.
I cannot compare then the way I'd like. ;) Consider the following: data BiMap a = BiMap { values :: Map Int a ,indices :: Map a Int } It will serve well for Int's, Bool's and Expr's. Then I decided to store typed Expr's, based on GADTs. Those Expr's contains type indices and it would be natural to classify BiMaps by their type indices and look up in there. If I require type indices to be Typeable, all I need is ordering on TypeRep. Also, I prototyped hypergraph library with hyperedges as types with type family as HList of types denoting labels. There I needed ordering on TypeRep too, again, for efficiency reasons.

On Sat, Dec 4, 2010 at 2:08 PM, Serguey Zefirov
Why TypeRep does have equality and doesn't have ordering?
It would be good to have that.
Yes, I have wanted that too. It would make maps from types to values possible/efficient. There is a very critical path in jhc that use type-indexed data structures that I have to implement a very hacky workaround for no Ord instance for TypeRep John

On 01:08 Sun 05 Dec , Serguey Zefirov wrote:
Why TypeRep does have equality and doesn't have ordering?
It would be good to have that.
I think the problem is, that it's hard to give an ordering that stays the same for all runs of your program. If you don't need this property you could use typeRepKey to give an instance as follows: instance Ord TypeRep where compare t1 t2 = compare (unsafePerformIO (typeRepKey t1)) (unsafePerformIO (typeRepKey t2)) I know it's not good style to use unsafePerformIO, but if you look at how typeRepKey is implemented I think it should be okay: typeRepKey :: TypeRep -> IO Int typeRepKey (TypeRep (Key i) _ _) = return i (The Eq instance also uses the key for comparison.)
Right now when I have to order two type representations I convert them to string and then compare. This is somewhat inefficient and not quite straightforward.
The implementation above should be efficient but should not be used when data between multiple runs since the ordering may change. Andreas

Thinking about this there might be one problem: Without having looked further into this I think perfomance might not be as expected. Using unsafePerformIO affects ghc's optimzations, doesn't it? So I wonder if it's a good idea (from a performance point of view) to use this.
2010/12/30 Andreas Baldeau
: instance Ord TypeRep where compare t1 t2 = compare (unsafePerformIO (typeRepKey t1)) (unsafePerformIO (typeRepKey t2))
typeRepKey :: TypeRep -> IO Int typeRepKey (TypeRep (Key i) _ _) = return i
So the question is, if ghc could transform this to simply compare the keys throwing away unsafePerformIO and return.

On 1 Jan 2011, at 12:38, Andreas Baldeau wrote:
Thinking about this there might be one problem:
Without having looked further into this I think perfomance might not be as expected. Using unsafePerformIO affects ghc's optimzations, doesn't it?
So I wonder if it's a good idea (from a performance point of view) to use this.
2010/12/30 Andreas Baldeau
: instance Ord TypeRep where compare t1 t2 = compare (unsafePerformIO (typeRepKey t1)) (unsafePerformIO (typeRepKey t2))
typeRepKey :: TypeRep -> IO Int typeRepKey (TypeRep (Key i) _ _) = return i
So the question is, if ghc could transform this to simply compare the keys throwing away unsafePerformIO and return.
Wouldn't a much better plan simply be to take typeRepKey out of the IO monad? Bob

On Saturday 01 January 2011 15:07:13, Thomas Davie wrote:
On 1 Jan 2011, at 12:38, Andreas Baldeau wrote:
So the question is, if ghc could transform this to simply compare the keys throwing away unsafePerformIO and return.
Wouldn't a much better plan simply be to take typeRepKey out of the IO monad?
I don't think so, it's in IO for a reason:
-- | Returns a unique integer associated with a 'TypeRep'. This can -- be used for making a mapping with TypeReps -- as the keys, for example. It is guaranteed that @t1 == t2@ -- if and only if @typeRepKey t1 == typeRepKey t2@. -- -- It is in the 'IO' monad because the actual value of the key may -- vary from run to run of the program. You should only rely on -- the equality property, not any actual key value. The relative -- ordering of keys has no meaning either. -- typeRepKey :: TypeRep -> IO Int
That also means that an Ord instance based on the keys may change from run to run. It's probably not a problem for applications if it's only used for storing TypeReps in a Map and not for programme logic (if typeOf 'a' < typeOf True then this else that), but it's somewhat fishy nevertheless.

On Sat, Jan 1, 2011 at 12:42 PM, Daniel Fischer
I don't think so, it's in IO for a reason:
-- | Returns a unique integer associated with a 'TypeRep'. This can -- be used for making a mapping with TypeReps -- as the keys, for example. It is guaranteed that @t1 == t2@ -- if and only if @typeRepKey t1 == typeRepKey t2@. -- -- It is in the 'IO' monad because the actual value of the key may -- vary from run to run of the program. You should only rely on -- the equality property, not any actual key value. The relative -- ordering of keys has no meaning either. -- typeRepKey :: TypeRep -> IO Int
That also means that an Ord instance based on the keys may change from run to run. It's probably not a problem for applications if it's only used for storing TypeReps in a Map and not for programme logic (if typeOf 'a' < typeOf True then this else that), but it's somewhat fishy nevertheless.
The reason for putting typeRepKey inside IO is changing between runs. So that means that compare should also be in IO. But, if you want to have a strang Ord instance, then why not have a strange unsafeTypeRepKey :: TypeRep -> Int? Cheers! -- Felipe.

On 13:04 Sat 01 Jan , Felipe Almeida Lessa wrote:
But, if you want to have a strang Ord instance, then why not have a strange unsafeTypeRepKey :: TypeRep -> Int?
Yes, that would be nice. But only if this really helps the compiler with optimising the code. Otherwise one could easily use unsafePerformIO. Andreas
participants (7)
-
Andreas Baldeau
-
Daniel Fischer
-
Felipe Almeida Lessa
-
John Meacham
-
Serguey Zefirov
-
Thomas Davie
-
Tianyi Cui