Dynamically altering sort order

Hi all, Suppose I have the following interface to a sorting function: sort :: (Ord a) => [a] -> IO [a] -- sort large, on-disk array of records but I don't have a sortBy where you can simply pass a compare function. Wrapped around this is a command-line program which should allow the user to specify different orderings on Records. For example, if the Record has three fields, the user should be able to say "sort only on the first two". Is there an Ord instance that can be dynamically changed in this way? My first idea is something like this: data CompareRecord = CR{ rCompare :: Record -> Record -> Ordering, unCR :: Record } instance Ord CompareRecord where compare (CR cmp x) (CR _ y) = cmp x y where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas? Thanks. Denis

Hi Denis, Denis Bueno wrote:
where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas?
Here's a solution that is more symmetrical but not necessarily prettier: newtype Wrap = Wrap { unwrap :: Record } instance Ord Wrap where ... your compare function here ... But I don't think there's anything wrong with your original solution. You can write your own sortBy and hide (not export) the CompareRecord type: sortBy :: (a -> a -> Ord) -> [a] -> IO [a] sortBy cmp = map unCR . sort . map (CompareRecord cmp) HTH, Martijn.

On Fri, Apr 24, 2009 at 15:22, Martijn van Steenbergen
Hi Denis,
Denis Bueno wrote:
where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas?
Here's a solution that is more symmetrical but not necessarily prettier:
newtype Wrap = Wrap { unwrap :: Record }
instance Ord Wrap where ... your compare function here ...
The problem here is that the order is fixed. Statically. I can't change it at runtime based on flags. (Right? Unless I'm missing something....)
But I don't think there's anything wrong with your original solution. You can write your own sortBy and hide (not export) the CompareRecord type:
sortBy :: (a -> a -> Ord) -> [a] -> IO [a] sortBy cmp = map unCR . sort . map (CompareRecord cmp)
Right, that's what I was thinking, too. The asymmetry was giving me the willies, though. =] Denis

Denis Bueno wrote:
The problem here is that the order is fixed. Statically. I can't change it at runtime based on flags. (Right? Unless I'm missing something....)
That is right. It might or might not be a problem in your specific case.
sortBy :: (a -> a -> Ord) -> [a] -> IO [a] sortBy cmp = map unCR . sort . map (CompareRecord cmp)
Right, that's what I was thinking, too. The asymmetry was giving me the willies, though. =]
Yeah, I know what you mean; it doesn't feel very elegant. :-) I'm curious if anyone else has any neat ideas. Martijn.

Denis Bueno wrote:
Hi all,
Suppose I have the following interface to a sorting function:
sort :: (Ord a) => [a] -> IO [a] -- sort large, on-disk array of records
but I don't have a sortBy where you can simply pass a compare function.
Why don't you have sortBy?
Wrapped around this is a command-line program which should allow the user to specify different orderings on Records. For example, if the Record has three fields, the user should be able to say "sort only on the first two".
Is there an Ord instance that can be dynamically changed in this way?
The only way to *dynamically* change the Ord instance is to have some language of newtypes wrapping records, each with and Ord instance. Then to have the user pass in a newtype name on the command line, parse that to know which constructor to use, map that constructor over the [a], and call sort. If you had a sortBy function, this could be extended a good deal by developing an AST language for expressing sorting functions, and then the user could specify the whole AST on the command line, you could parse the string into an AST and then have a function to interpret the AST as a sorting function which you then pass to sortBy. Actually, this sounds like a fun little program to add to the Unix toolbox. If, however, you wanted to (statically) derive a sortBy function given only the sort function, then you only need one Ord instance: namely one that packages up a comparison function with the values, as with your idea: (but...)
My first idea is something like this:
data CompareRecord = CR{ rCompare :: Record -> Record -> Ordering, unCR :: Record } instance Ord CompareRecord where compare (CR cmp x) (CR _ y) = cmp x y
where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry.
More than just an ugly asymmetry, it's easy to get bugs here because there's no assurance that we have the same comparison function packaged up on both sides, and so that means 'compare' is no longer commutative. If you define sortBy using the Schwartzian transform like Martijn suggested, though, then we can show that at least it's right for this use case. -- Live well, ~wren

On Fri, Apr 24, 2009 at 5:11 PM, Denis Bueno
Hi all,
Suppose I have the following interface to a sorting function:
sort :: (Ord a) => [a] -> IO [a] -- sort large, on-disk array of records
but I don't have a sortBy where you can simply pass a compare function.
Wrapped around this is a command-line program which should allow the user to specify different orderings on Records. For example, if the Record has three fields, the user should be able to say "sort only on the first two".
Is there an Ord instance that can be dynamically changed in this way?
My first idea is something like this:
data CompareRecord = CR{ rCompare :: Record -> Record -> Ordering, unCR :: Record } instance Ord CompareRecord where compare (CR cmp x) (CR _ y) = cmp x y
where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas?
You can make a safer 'CompareRecord' using 'reflection' from hackage:
{-# LANGUAGE TypeOperators, FlexibleContexts, UndecidableInstances #-}
import Data.Reflection import Data.List (sort)
myList = [1,2,5,4,2]
newtype (s `Ordered` a) = Ordered { getOrdered :: a }
instance (s `Reflects` (a -> a -> Ordering)) => Eq (s `Ordered` a) where a == b = (a `compare` b) == EQ
instance (s `Reflects` (a -> a -> Ordering)) => Ord (s `Ordered` a) where a `compare` b = reflect (undefined `asReifiedComparison` a) (getOrdered a) (getOrdered b) where asReifiedComparison :: s -> (s `Ordered` a) -> s asReifiedComparison = const
-- for expository purposes, I renamed your sort, 'mySort' and aped it with the Data.List sort
mySort :: Ord a => [a] -> IO [a] mySort = return . sort
withOrder :: s -> a -> s `Ordered` a withOrder = const Ordered
mySortBy :: (a -> a -> Ordering) -> [a] -> IO [a] mySortBy f as = reify f (\s -> map getOrdered `fmap` mySort (map (withOrder s) as))
test1 = mySortBy compare myList test2 = mySortBy (flip compare) myList
*Main> test1 Loading package reflection-0.1.1 ... linking ... done. [1,2,2,4,5] *Main> test2 [5,4,2,2,1] The sort function is lifted up to the type level by 'reify' and is extracted uniformly by 'reflect' 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. -Edward Kmett

On Fri, Apr 24, 2009 at 19:49, Edward Kmett
On Fri, Apr 24, 2009 at 5:11 PM, Denis Bueno
wrote: Is there an Ord instance that can be dynamically changed in this way?
My first idea is something like this:
data CompareRecord = CR{ rCompare :: Record -> Record -> Ordering, unCR :: Record } instance Ord CompareRecord where compare (CR cmp x) (CR _ y) = cmp x y
where the rCompare field would be a function that is based on the flags passed to the command-line problem. But this has an ugly asymmetry. Does anyone have any other ideas?
You can make a safer 'CompareRecord' using 'reflection' from hackage:
This is what I ended up doing and it worked out great. Thanks for the suggestion. Denis
participants (4)
-
Denis Bueno
-
Edward Kmett
-
Martijn van Steenbergen
-
wren ng thornton