Traversal order newtypes for Data.Tree, and Ord instances

Data.Tree.Tree has Foldable and Traversable instances for traversing a tree in preorder. Should we add the derived Ord instance to match? Should we offer newtypes for traversing in post-order and level-order with Eq and Ord instances to match? I've made coercions explicit below, rather than relying on map/coerce rules, to make performance characteristics clearer. deriving instance Ord a => Ord (Tree a) newtype PostOrder a = PostOrder {getPostOrder :: Tree a} deriving (Show, Read, Functor) instance Foldable PostOrder where foldMap f (PostOrder (Node a ts)) = foldMap (foldMap f . PostOrder) ts <> f a instance Traversable PostOrder where traverse f (PostOrder (Node a ts)) = (\ts' a' -> PostOrder (Node a' (coerce ts'))) <$> traverse (traverse f . PostOrder) ts <*> f a instance Eq a => Eq (PostOrder a) where PostOrder a1 ts1 == PostOrder a2 ts2 = (coerce `asTypeOf` map PostOrder) ts1 == coerce ts2 && a1 == a2 instance Ord a => Ord (PostOrder a) where PostOrder a1 ts1 `compare` PostOrder a2 ts2 = ((coerce `asTypeOf` map PostOrder) ts1 `compare` coerce ts2) <> (a1 `compare` a2) newtype LevelOrder a = LevelOrder {getLevelOrder :: Tree a} deriving (Show, Read, Functor) I'm still working out the best ways to perform level-order folds and traversals. One option for Foldable is instance Foldable LevelOrder where foldr c n (LevelOrder (Node a ts)) = a `c` frlof c n ts where frlof :: (a -> b -> b) -> b -> [Tree a] -> b frlof _c n [] = n frlof c n ts = roots where (roots, forest) = uzt c (frlof c n forest) ts uzt :: (a -> b -> b) -> b -> [Tree a] -> (b, [Tree a]) uzt _c n [] = (n, []) uzt c n (Node a fr : ts) = (a `c` n', fr ++ ts') where (n', ts') = uzt c n ts David Feuer
participants (1)
-
David Feuer