[Haskell-cafe] Generic Sorting
Henry Laxen
nadine.and.henry at pobox.com
Sat Nov 14 17:30:52 UTC 2020
>>>>> "jack" == jack <jack at jackkelly.name> writes:
Henry> November 14, 2020 2:08 PM, "Henry Laxen" <nadine.and.henry at pobox.com> wrote:
Henry> I've done some searching but so far haven't found anything, which make
Henry> me think this probably isn't possible. I am wondering if it is
Henry> possible to do a "Generic Sort" on multilevel data structures.
Henry> Suppose you have something like:
jack> This is not quite what you asked for, but might get you started. It's based on a trick that Alex Mason once showed me:
jack> {-# LANGUAGE AllowAmbiguousTypes #-}
jack> {-# LANGUAGE DeriveDataTypeable #-}
jack> {-# LANGUAGE ScopedTypeVariables #-}
jack> import Control.Lens
jack> import Data.Data
jack> import Data.Data.Lens
jack> import Data.List
jack> data A = A Int [Int] deriving (Data, Show)
jack> data B = B Int [A] deriving (Data, Show)
jack> a1 = A 2 [2,1]
jack> a2 = A 1 [4,3]
jack> b = B 1 [a1,a2]
jack> -- | oh no
jack> -- >>> genericSort @Int b
jack> -- B 1 [A 1 [1,2],A 2 [3,4]]
jack> genericSort :: forall a d . (Data d, Typeable a, Ord a) => d -> d
jack> genericSort = partsOf template %~ (sort :: [a] -> [a])
Henry> Note that it's sorted every Int anywhere in the structure, not just the ones inside an A.
Wow Jack, that looks like magic. I'm going to read about partsOf and
template, which I've never used before. One thing, to actuall run it you need
to add {-# LANGUAGE TypeApplications #-} so you can say "genericSort @Int b".
Thanks so much for your quick and brilliant response.
Best wishes,
Henry Laxen
More information about the Haskell-Cafe
mailing list