Question about abstraction

Dear list, I have I question about the following code I was playing with: (you can past the following right into your editor) ---------------------------------------------------------------------- import Data.Foldable (Foldable, foldMap) import Data.Monoid (mempty, mappend) import Data.Traversable (Traversable, traverse) import Control.Applicative (pure, (<$>), (<*>)) -- I was playing with the following tree-like datastructure (my plan -- is to make some kind of kd-tree but that's not important now): data T a = L | N C2 a (T a) (T a) (T a) (T a) type C2 = (Float, Float) -- A fold always comes in handy: foldT :: b -> (C2 -> a -> b -> b -> b -> b -> b) -> T a -> b foldT e _ L = e foldT e n (N c x tl tr bl br) = n c x (foldT e n tl) (foldT e n tr) (foldT e n bl) (foldT e n br) instance Functor T where fmap f = foldT L (\p -> N p . f) -- Now I defined the following instances: instance Foldable T where foldMap f = foldT mempty $ \_ x tl tr bl br -> f x `mappend` tl `mappend` tr `mappend` bl `mappend` br instance Traversable T where traverse f = foldT (pure L) $ \p x tl tr bl br -> N p <$> f x <*> tl <*> tr <*> bl <*> br ---------------------------------------------------------------------- -- If you look at the previous two functions you see a similar pattern: -- they both combine an initial value: 'f x' and 'N p <$> f x' respectively -- with the childs using a combining function: 'mappend' and '<*>' respectively. -- My question is: can I abstract from that? -- It looks like I can using a function like: combineWith :: b -> (b -> a -> b) -> a -> a -> a -> a -> b n `combineWith` f = \tl tr bl br -> n `f` tl `f` tr `f` bl `f` br -- Now 'foldMap' becomes: instance Foldable T where foldMap f = foldT mempty $ \_ x -> f x `combineWith` mappend -- But 'traverse' won't typecheck: instance Traversable T where traverse f = foldT (pure L) $ \p x -> (N p <$> f x) `combineWith` (<*>) -- Is it possible to make 'combineWith' more general so that the -- previous typechecks (maybe using arbitrary-rank polymorphism but I -- don't see how)? ---------------------------------------------------------------------- Thanks, Bas van Dijk

combineWith :: b -> (b -> a -> b) -> a -> a -> a -> a -> b n `combineWith` f = \tl tr bl br -> n `f` tl `f` tr `f` bl `f` br
instance Foldable T where foldMap f = foldT mempty $ \_ x -> f x `combineWith` mappend
-- But 'traverse' won't typecheck:
instance Traversable T where traverse f = foldT (pure L) $ \p x -> (N p <$> f x) `combineWith` (<*>)
-- Is it possible to make 'combineWith' more general so that the -- previous typechecks (maybe using arbitrary-rank polymorphism but I -- don't see how)?
Looks tempting, doesn't it?-) But while the code is the same, the types needed for the two uses are rather different (and the inferred type not the most general one): combineWith :: b -> (b -> a -> b) -> (a -> a-> a-> a-> b) combineWith :: f (a->a->a->a->b) -> (forall a b . f (a->b) -> f a -> f b) -> (f a->f a->f a->f a->f b) We can shorten them a bit: type Four a b = a -> a -> a -> a -> b combineWith :: b -> (b -> a -> b) -> Four a b combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) and we can add a dummy constructor to make them more similar: newtype Id a = Id{unId::a} combineWith :: f b -> ( f b -> f a -> f b) -> Four (f a) (f b) -- f ~ Id combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) which leaves us with the crux of the matter: the function parameters and their uses are completely different: four independent applications of mappend vs four accumulating applications of (<*>). We still can make the simple case look like the complex case, by moving the mappend to the first parameter, but whether that is helpful is another question: combineWith :: f (Four a b) -> (forall a b . f (a->b) -> f a -> f b) -> Four (f a) (f b) n `combineWith` f = \tl tr bl br -> n `f` tl `f` tr `f` bl `f` br four f a b c d e = f (f (f (f a b) c) d) e instance Foldable T where foldMap f = unId . foldT (Id mempty) (\_ x -> Id (four mappend $ f x) `combineWith` (\(Id a) (Id b)->Id (a b))) instance Traversable T where traverse f = foldT (pure L) $ \p x -> (N p <$> f x) `combineWith` (<*>) Slightly more interesting is that foldMap should be an application of traverse (see Traversable documentation, and its source, for foldMapDefault). Hth, Claus
participants (2)
-
Bas van Dijk
-
Claus Reinke