
Dear All, I am trying to produce a Map, where the (tricky) idea is that the key is a pair, (t1, t2), and the key is considered identical under ordering. Thus: (t1, t2) is the same as (t2, t1) but (t1, t3) is not the same as (t1,t2). This LOOKS like a equality definition. However, the Map key typeclass is defined as Ord, which requires me to define compare: instance Ord Edge where (Edge s1 _) `compare` (Edge s2 _) = s1 `compare` s2 I am a bit stuck on how to use compare to define this type of eqlaity - any pointers very gratefully received. BW, Matt

What about using new type and sort the pair before comparing?
Dne 26.6.2015 15:56 "Matt Williams"
Dear All,
I am trying to produce a Map, where the (tricky) idea is that the key is a pair, (t1, t2), and the key is considered identical under ordering. Thus:
(t1, t2) is the same as (t2, t1) but (t1, t3) is not the same as (t1,t2).
This LOOKS like a equality definition. However, the Map key typeclass is defined as Ord, which requires me to define compare:
instance Ord Edge where (Edge s1 _) `compare` (Edge s2 _) = s1 `compare` s2
I am a bit stuck on how to use compare to define this type of eqlaity - any pointers very gratefully received.
BW,
Matt
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Fri, Jun 26, 2015 at 9:55 AM, Matt Williams wrote: I am trying to produce a Map, where the (tricky) idea is that the key is a
pair, (t1, t2), and the key is considered identical under ordering. Thus: (t1, t2) is the same as (t2, t1) but
(t1, t3) is not the same as (t1,t2). This LOOKS like a equality definition. However, the Map key typeclass is
defined as Ord, which requires me to define compare: You need more than Eq to get a collection which can be searched
efficiently. Map uses Ord; Hashmap (in unordered-containers) uses Hashable,
and might be more appropriate for this type. You will still have to deal
with the pair, however.
Ord (or Hashable) is only used internally for searching, so you can define
an instance which does not necessarily do anything semantically meaningful.
For example, one way to define a `compare` for this is to sort the values
in the pairs and then apply compare between them:
-- assumes s, t are themselves known by compiler to be Ord
instance Ord Edge where
(Edge s1 t1) `compare` (Edge s2 t2) = let arb s t = if s < t then
(s,t) else (t,s)
in arb s1 t1 `compare` arb
s2 t2
A similar trick could be used to get a Hashable instance.
This would end up being slow for large maps or many lookups. In that case,
you might consider a wrapper which applies the above "arb" operation to the
key on insert or lookup (the "normalized" key is stored in the map), rather
than having to compute it for every node traversed during lookup.
--
brandon s allbery kf8nh sine nomine associates
allbery.b@gmail.com ballbery@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (4)
-
Brandon Allbery
-
Imants Cekusins
-
Matt Williams
-
Petr Vápenka