nonfree-0.1.0.1: Free structures sans laws

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Monoid.Nonfree

Description

A free "monoid sans laws" type (i.e., a "free pointed magma") with an illegal Monoid instance, intended for debugging.

An example use: We can see that the Foldable instance for Data.Map in containers-0.5.0.0 generates a lot of memptys (one per leaf):

> foldMap N (M.fromList [(x,x) | x <- [1..5]])
(((ε ◇ N 1) ◇ ε) ◇ N 2) ◇ ((((ε ◇ N 3) ◇ ε) ◇ N 4) ◇ ((ε ◇ N 5) ◇ ε))

After a discussion with the maintainer, this is improved in containers-0.5.5.1:

> foldMap N (M.fromList [(x,x) | x <- [1..5]])
(N 1 ◇ (N 2 ◇ N 3)) ◇ (N 4 ◇ N 5)

But now we can see a discrepancy between the Foldable and Traversable instances:

> foldMapDefault N (M.fromList [(x,x) | x <- [1..5]])
(((N 1 ◇ N 2) ◇ N 3) ◇ N 4) ◇ N 5

This is because an expression like f <$> x <*> y <*> z generates a left-biased tree -- (x <> y) <> z -- whereas the Foldable instance makes a right-biased tree -- x <> (y <> z).

Due to the monoid laws, these sorts of issues are typically invisible unless you look for them. But they can make a performance difference.

Synopsis

Documentation

data N a Source

Nonfree nonmonoid.

Constructors

N a 
NEmpty 
NAppend (N a) (N a) 

Instances

Functor N 
Foldable N 
Traversable N 
Show a => Show (N a)

The Show instance uses short names to make the append trees readable.

Monoid (N a) 

(◇) :: Monoid m => m -> m -> m Source

A synonym for mappend (<>).

ε :: Monoid m => m Source

A synonym for mempty.

toN :: Foldable t => t a -> N a Source

A version of toList that extracts the full monoid append tree rather than flattening it to a list.

fromN :: Traversable t => N b -> t a -> t b Source

Given a monoid append tree and a Traversable structure with exactly the same shape, put values from the former into the latter. This will fail with an error if the structure isn't identical.