Skip to content

Instantly share code, notes, and snippets.

@robrix
Created June 20, 2020 15:10
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save robrix/b7b74aad2766f3e63b89219bf6c88596 to your computer and use it in GitHub Desktop.
Save robrix/b7b74aad2766f3e63b89219bf6c88596 to your computer and use it in GitHub Desktop.
Single-pass folding of multiple structures.
module Data.FoldableN where
import Control.Applicative -- for ZipList
import Linear.V1 -- for V1, an identity functor
import Linear.V2 -- for V2, data V2 a = V2 a a
class Foldable t => FoldableN t where
-- | Fold multiple structures into a 'Monoid'.
--
-- @
-- foldMap2 f a b = fold (liftA2 f a b)
-- @
foldMap2 :: Monoid m => (a -> b -> m) -> t a -> t b -> m
-- | we can fold identity functors
instance FoldableN V1 where
foldMap2 f (V1 a) (V1 b) = f a b
-- | we can fold products with multiple fields of the parameter type
instance FoldableN V2 where
foldMap2 f (V2 ax ay) (V2 bx by) = f ax bx <> f ay by
-- | we can ignore extra structure in products
instance FoldableN ((,) a) where
foldMap2 f (_, a) (_, b) = f a b
-- | we can combine sums multiplicatively
instance FoldableN Maybe where
foldMap2 f (Just a) (Just b) = f a b
foldMap2 _ _ _ = mempty
-- | we have two possible instances for lists, corresponding to the 'Applicative' instances for [] and 'ZipList'
instance FoldableN [] where
foldMap2 f (x:xs) ys = foldMap (f x) ys <> foldMap2 f xs ys
foldMap2 _ _ _ = mempty
-- | I don’t know whether to expect that this is more useful than the other one or not
instance FoldableN ZipList where
foldMap2 f (ZipList (x:xs)) (ZipList (y:ys)) = f x y <> foldMap2 f (ZipList xs) (ZipList ys)
foldMap2 _ _ _ = mempty
@robrix
Copy link
Author

robrix commented Jun 20, 2020

Open question: does foldMap2 suffice to define foldMap3, foldMap4, etc., in the same manner as liftA2 suffices to define liftA3, liftA4, etc.?

@robrix
Copy link
Author

robrix commented Jun 21, 2020

Open question: does foldMap2 suffice to define foldMap3, foldMap4, etc., in the same manner as liftA2 suffices to define liftA3, liftA4, etc.?

It does indeed:

foldMap3 :: (FoldableN t, Monoid m) => (a -> b -> c -> m) -> t a -> t b -> t c -> m
foldMap3 f a b = foldMap (foldMap2 f a b)

@robrix
Copy link
Author

robrix commented Jun 21, 2020

One can also define foldMap2 with only foldMap!

foldMap2 :: (Foldable t, Monoid m) => (a -> b -> m) -> t a -> t b -> m
foldMap2 f a b = foldMap (foldMap f a) b

@robrix
Copy link
Author

robrix commented Jun 21, 2020

To define traverse2, however, one additionally needs a Monad instance for t:

traverse2 :: (Monad t, Traversable t, Applicative f) => (a -> b -> f c) -> t a -> t b -> f (t c)
traverse2 f a b = join <$> traverse (for b . f) a

@robrix
Copy link
Author

robrix commented Jun 22, 2020

@snowleopard points out that an Applicative instance suffices:

traverse2 :: (Applicative t, Traversable t, Applicative f) => (a -> b -> f c) -> t a -> t b -> f (t c)
traverse2 f a b = traverse (uncurry f) (liftA2 (,) a b)

This is, in fact, precisely the desired semantics—see for example the law given for foldMap2, above.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment