<div class="gmail_quote">On Fri, Apr 24, 2009 at 5:11 PM, Denis Bueno <span dir="ltr">&lt;<a href="mailto:dbueno@gmail.com">dbueno@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
Hi all,<br>
<br>
Suppose I have the following interface to a sorting function:<br>
<br>
    sort :: (Ord a) =&gt; [a] -&gt; IO [a] -- sort large, on-disk array of records<br>
<br>
but I don&#39;t have a sortBy where you can simply pass a compare function.<br>
<br>
Wrapped around this is a command-line program which should allow the<br>
user to specify different orderings on Records.  For example, if the<br>
Record has three fields, the user should be able to say &quot;sort only on<br>
the first two&quot;.<br>
<br>
Is there an Ord instance that can be dynamically changed in this way?<br>
<br>
My first idea is something like this:<br>
<br>
    data CompareRecord = CR{ rCompare :: Record -&gt; Record -&gt; Ordering,<br>
unCR :: Record }<br>
    instance Ord CompareRecord where<br>
        compare (CR cmp x) (CR _ y) = cmp x y<br>
<br>
where the rCompare field would be a function that is based on the<br>
flags passed to the command-line problem.  But this has an ugly<br>
asymmetry.  Does anyone have any other ideas?<br></blockquote><div><br></div><div>You can make a safer &#39;CompareRecord&#39; using &#39;reflection&#39; from hackage:</div><div><br></div><div><br></div><div><br></div><div>
<br></div><div><div>&gt; {-# LANGUAGE TypeOperators, FlexibleContexts, UndecidableInstances #-}</div><div><br></div><div>&gt; import Data.Reflection</div><div>&gt; import Data.List (sort)<br></div><div><br></div><div>&gt; myList = [1,2,5,4,2]</div>
<div><br></div><div>&gt; newtype (s `Ordered` a) = Ordered { getOrdered :: a }</div><div><br></div><div>&gt; instance (s `Reflects` (a -&gt; a -&gt; Ordering)) =&gt; Eq (s `Ordered` a) where</div><div>&gt;    a == b = (a `compare` b) == EQ</div>
<div><br></div><div>&gt; instance (s `Reflects` (a -&gt; a -&gt; Ordering)) =&gt; Ord (s `Ordered` a) where</div><div>&gt;    a `compare` b = reflect (undefined `asReifiedComparison` a) </div><div>&gt;                            (getOrdered a) (getOrdered b) </div>
<div>&gt;      where</div><div>&gt;        asReifiedComparison :: s -&gt; (s `Ordered` a) -&gt; s</div><div>&gt;        asReifiedComparison = const</div><div><br></div><div>-- for expository purposes, I renamed your sort, &#39;mySort&#39; and aped it with the Data.List sort</div>
<div><br></div><div>&gt; mySort :: Ord a =&gt; [a] -&gt; IO [a]</div><div>&gt; mySort = return . sort</div><div><br></div><div>&gt; withOrder :: s -&gt; a -&gt; s `Ordered` a </div><div>&gt; withOrder = const Ordered</div>
<div><br></div><div>&gt; mySortBy :: (a -&gt; a -&gt; Ordering) -&gt; [a] -&gt; IO [a]</div><div>&gt; mySortBy f as = reify f (\s -&gt; map getOrdered `fmap` mySort (map (withOrder s) as))</div><div><br></div><div>&gt; test1 = mySortBy compare myList</div>
<div>&gt; test2 = mySortBy (flip compare) myList</div><div><br></div><div><div>*Main&gt; test1</div><div>Loading package reflection-0.1.1 ... linking ... done.</div><div>[1,2,2,4,5]</div><div><br></div><div>*Main&gt; test2</div>
<div>[5,4,2,2,1]</div><div><br></div></div><div>The sort function is lifted up to the type level by &#39;reify&#39; and is extracted uniformly by &#39;reflect&#39; eliminating the bias or your first proposed implementation. Note that the mapping of withOrder is just to force them all to agree on the type parameter s.<br>
<br></div><div>-Edward Kmett</div></div></div>