
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