
November 14, 2020 2:08 PM, "Henry Laxen"
I've done some searching but so far haven't found anything, which make me think this probably isn't possible. I am wondering if it is possible to do a "Generic Sort" on multilevel data structures. Suppose you have something like:
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: {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ScopedTypeVariables #-} import Control.Lens import Data.Data import Data.Data.Lens import Data.List data A = A Int [Int] deriving (Data, Show) data B = B Int [A] deriving (Data, Show) a1 = A 2 [2,1] a2 = A 1 [4,3] b = B 1 [a1,a2] -- | oh no -- >>> genericSort @Int b -- B 1 [A 1 [1,2],A 2 [3,4]] genericSort :: forall a d . (Data d, Typeable a, Ord a) => d -> d genericSort = partsOf template %~ (sort :: [a] -> [a]) Note that it's sorted every Int anywhere in the structure, not just the ones inside an A. HTH, -- Jack