Proposal: Add "Alternative" instance for ZipList, as well as Semigroup and Monoid

Zemyla zemyla at gmail.com
Sat Oct 21 18:00:15 UTC 2017


This paper on monoids and near-semirings gives an Alternative instance
for ZipList consistent with its Applicative instance:

https://lirias.kuleuven.be/bitstream/123456789/499951/1/main.pdf

The original definition of (<|>) leaves a lot to be desired, because
it iterates through the first list twice, preventing inlining of xs:

ZipList xs <|> ZipList ys = ZipList $ xs ++ drop (length xs) ys

Edited for efficiency, it winds up being:

instance Alternative ZipList where
  empty = ZipList []

  ZipList xs <|> ZipList ys = ZipList $ go xs ys where
    go [] ys = ys
    go xs [] = xs
    go (x:xs) (_:ys) = x:go xs ys

A different formulation, using foldr/build, goes like this:

ZipList xs <|> ZipList ys = ZipList $ build $ \c z -> let
  goX x xr !n = c x $ xr $ n + 1
  goY y yr n
    | n <= 0 = c y $ yr 0
    | otherwise = yr $ n - 1
  in foldr goX (foldr goY (const z) ys) ys (0 :: Int)

It is an idempotent monoid, and sconcat/mconcat can be written as follows:

zlconcat :: Foldable t => t (ZipList a) -> ZipList a
zlconcat xss = ZipList $ build $ \c z -> let
  goO (ZipList xs) xr !n = foldr goI endI xs 0 where
    goI x xk i
      | i < n = xk $ i + 1
      | otherwise = c x $ xk $ i + 1
    endI i = if i < n then xr n else xr i
  in foldr goO (const z) xss (0 :: Int)

So in the end, the Semigroup/Monoid instances look like:

instance Semigroup (ZipList a) where
  (<>) = (<|>)

  sconcat = zlconcat

  stimes = stimesIdempotentMonoid

instance Monoid (ZipList a) where
  mempty = empty

  mappend = (<|>)

  mconcat = zlconcat

Sadly, the paper doesn't prove that it's a valid left catch
Alternative, and sort of mentions it offhand, but tests suggest it is
associative, [] is obviously the identity for <|> and the zero for
<*>, and pure a <|> x = pure a.

Any ideas on which implementation to prefer, or different ideas for
implementing sconcat/mconcat?


More information about the Libraries mailing list