Reputation: 3434
I'm wondering if there are general ways to convert between ad-hoc polymorphic functions and parametric polymorphic ones. In other words, given an ad-hoc polymorphic function, how to implement its parametric counterpart? and what about the other way around?
take sort
as an example. it's easy to write sort :: Ord a => [a] -> [a]
in terms of sortBy
:
sort :: Ord a => [a] -> [a]
sort = sortBy compare
but the other way around seems tricky, so far the best I can do is to go a bit "object-oriented":
import qualified Data.List as L
data OrdVal a = OV (a -> a -> Ordering) a
instance Eq (OrdVal a) where
(OV cmp a) == (OV _ b) = a `cmp` b == EQ
instance Ord (OrdVal a) where
(OV cmp a) `compare` (OV _ b) = a `cmp` b
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
sortBy cmp = map unOV . L.sort . map (OV cmp)
where
unOV (OV _ v) = v
But this sounds more like a hack than proper solution.
so I'd like to know:
Upvotes: 10
Views: 363
Reputation: 27636
I'm not necessarily saying you should do this, but you can use reflection to pass around the comparison function without having to package it up with each element of the list:
{-# LANGUAGE UndecidableInstances #-}
import Data.Reflection
newtype O a = O a
instance Given (a -> a -> Ordering) => Eq (O a) where
x == y = compare x y == EQ
instance Given (a -> a -> Ordering) => Ord (O a) where
compare (O x) (O y) = given x y
Given (heh) the above infrastructure, you can then write sortBy
in terms of sort
as follows:
import Data.Coerce
import Data.List (sort)
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
sortBy cmp = give cmp $ from . sort . to
where
to :: [a] -> [O a]
to = coerce
from :: [O a] -> [a]
from = coerce
(note that by using Data.Coerce
, we avoid all potential runtime cost of the O
wrapper)
Upvotes: 8
Reputation: 48611
Cactus's answer relies on the somewhat shady Given
class in reflection
. It's possible, however, to use reflection without that.
{-# LANGUAGE ScopedTypeVariables, MultiParamTypeClasses, UndecidableInstances #-}
module SortReflection where
import Data.Reflection
import Data.List (sort)
import Data.Proxy
import Data.Coerce
newtype O s a = O {getO :: a}
instance Reifies s (a -> a -> Ordering) => Eq (O s a) where
a == b = compare a b == EQ
instance Reifies s (a -> a -> Ordering) => Ord (O s a) where
compare = coerce (reflect (Proxy :: Proxy s))
sortBy :: forall a . (a -> a -> Ordering) -> [a] -> [a]
sortBy cmp = reify cmp $
\(_ :: Proxy s) -> coerce (sort :: [O s a] -> [O s a])
Examining the Core produced indicates that this compiles to a thin wrapper around sortBy
. It looks even thinner using a Reifies
class based on Tagged
instead of Proxy
, but Ed Kmett doesn't like the API that produces.
Upvotes: 6