nonfree-0.1.0.4: Free structures sans laws

Safe HaskellSafe
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 Source # 
Instance details

Defined in Data.Monoid.Nonfree

Methods

fmap :: (a -> b) -> N a -> N b #

(<$) :: a -> N b -> N a #

Foldable N Source # 
Instance details

Defined in Data.Monoid.Nonfree

Methods

fold :: Monoid m => N m -> m #

foldMap :: Monoid m => (a -> m) -> N a -> m #

foldr :: (a -> b -> b) -> b -> N a -> b #

foldr' :: (a -> b -> b) -> b -> N a -> b #

foldl :: (b -> a -> b) -> b -> N a -> b #

foldl' :: (b -> a -> b) -> b -> N a -> b #

foldr1 :: (a -> a -> a) -> N a -> a #

foldl1 :: (a -> a -> a) -> N a -> a #

toList :: N a -> [a] #

null :: N a -> Bool #

length :: N a -> Int #

elem :: Eq a => a -> N a -> Bool #

maximum :: Ord a => N a -> a #

minimum :: Ord a => N a -> a #

sum :: Num a => N a -> a #

product :: Num a => N a -> a #

Traversable N Source # 
Instance details

Defined in Data.Monoid.Nonfree

Methods

traverse :: Applicative f => (a -> f b) -> N a -> f (N b) #

sequenceA :: Applicative f => N (f a) -> f (N a) #

mapM :: Monad m => (a -> m b) -> N a -> m (N b) #

sequence :: Monad m => N (m a) -> m (N a) #

Show a => Show (N a) Source #

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

Instance details

Defined in Data.Monoid.Nonfree

Methods

showsPrec :: Int -> N a -> ShowS #

show :: N a -> String #

showList :: [N a] -> ShowS #

Semigroup (N a) Source # 
Instance details

Defined in Data.Monoid.Nonfree

Methods

(<>) :: N a -> N a -> N a #

sconcat :: NonEmpty (N a) -> N a #

stimes :: Integral b => b -> N a -> N a #

Monoid (N a) Source # 
Instance details

Defined in Data.Monoid.Nonfree

Methods

mempty :: N a #

mappend :: N a -> N a -> N a #

mconcat :: [N a] -> 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.