List monads in general
class Monad m => ListMonad m where Source #
In this module, a "list monad" is a monad in which the underlying functor is isomorphic to List. We require:
wrap . unwrap == id unwrap . wrap == id
There is a default implementation provided if m is known to be a
list (meaning m a is an instance of IsList for all
a).
Minimal complete definition
Nothing
newtype DualListMonad m a Source #
Every list monad has a dual, in which join is defined as
join . reverse . fmap reverse
(where join is the join of the original list monad), while return is
reverse . return
(where return is the return of the original list monad).
Monads with finite presentation
This section contains monads that come about from free algebras of
theories with a finite number of operations, represented as type
classes. Coincidentally, all theories in this module have one
binary and one nullary operation, that is, each is a subclass of
PointedMagma with additional laws. (So does the usual list monad,
where the subclass is monoid.) It is not known if there exists a
list monad that have a finite presentation but necessarily with a
different set of operations (there are such monads on non-empty
lists, for example, HeadTails
and HeadsTail).
Pointed magmas
class PointedMagma a where Source #
Pointed magmas are structures with one binary operation and one constant. In general, no laws are imposed.
class ListMonad m => FreeRBPM m (c :: * -> Constraint) | m -> c where Source #
A class for free right-braketed (subclasses of) pointed magmas.
Most of the monads defined in this module arise from subclasses of
PointedMagma, in which we do not assume any additional methods,
but require the instances to satisfy additional equations. This
means that the monad is not only an instance of such a class that
defines a type of algebra, but it is free such algebra.
In particular, we consider theories c in which the equations have
the following shapes:
x<>eps== ...eps<>x == ... (x<>y)<>z == ...
Moreover, when read left-to-right, they form a terminating and confluent rewriting system with normal forms of the following shape:
epsx<>(y<>( ... (z<>t) ... ))
This class offers a witness that a particular list monad m is a free algebra of
the theory c. This gives us the function
foldRBPM _ (unwrap-> []) =epsfoldRBPM f (unwrap-> xs) =foldr1(<>) (mapf xs)
which is the unique lifting of an interpretation of generators to a
homomorphism (between algebras of this sort) from the list monad to
any algebra (an instance) of c.
Note that the default definition of foldRBPM is always the right
one for right-bracketed subclasses of PointedMagma, so it is
enough to declare the relationship, for example:
instance FreeRBPM [] Monoid
Minimal complete definition
Nothing
The Global Failure monad
newtype GlobalFailure a Source #
The Global Failure monad arises from free zero semigroups. It implements a kind of nondeterminism similar to the usual List monad, but failing (= producing an empty list) in one branch makes the entire computation fail. Its join is defined as:
join xss | any null xss = []
| otherwise = concat xss
For example:
>>>[1, 2, 3] >>= (\n -> [1..n]) :: GlobalFailure IntGlobalFailure [1,1,2,1,2,3]>>>[1, 0, 3] >>= (\n -> [1..n]) :: GlobalFailure IntGlobalFailure []
The Maze Walk monad
palindromize :: [a] -> [a] Source #
Turns a list into a palindrome by appending it and its reversed init. For example:
palindromize [] == [] palindromize "Ringo" == "RingogniR"
The Maze Walk monad arises from free palindrome algebras. Its join is defined as:
join xss | null xss = []
| any null xss = []
| otherwise = concatMap palindromize (init xss) ++ last xss
Intuitively, it is a list of values one encounters when walking a path in a maze. The bind operation attaches to each value a new "corridor" to visit. In our walk we explore every such corridor. For example, consider the following expression:
>>>join ["John", "Paul", "George", "Ringo"] :: MazeWalk CharMazeWalk "JohnhoJPauluaPGeorgegroeGRingo"
It represents a walk through the following maze (the entrance is marked with ">"):
┌────┬──────┐
│L U │ N G O│
├─┤A ┴ I┌───┘
> J P G R│
┌─┘O ┬ E ┌┘
│N H │ O └──┐
└────┤ R G E│
└──────┘
First, we take the J-O-H-N path. When we reach its end, we turn around and go back to J, so our walk to this point is J-O-H-N-H-O-J (hence the connection with palindromes). Then, we explore the P-A-U-L corridor, adding P-A-U-L-U-A-P to our walk. The same applies to G-E-O-R-G-E. But when at the end of R-I-N-G-O, we have explored the entire maze, so our walk is done (this is why we do not palindromize the last element).
The Discrete Hybrid monad
safeLast :: [a] -> [a] Source #
A singleton list with the last element of the argument, if it exists. Otherwise, empty.
safeLast "Roy" == "y" safeLast [] == []
newtype DiscreteHybrid a Source #
The Discrete Hybrid monad arises from free leaning algebras. Its join is defined as:
join xss | null xss = []
| null (last xss) = []
| otherwise = concatMap safeLast (init xss) ++ last xss
For example:
>>>join ["Roy", "Kelton", "Orbison"] :: DiscreteHybrid CharDiscreteHybrid "ynOrbison">>>join ["Roy", "", "Orbison"] :: DiscreteHybrid CharDiscreteHybrid "yOrbison"
Different versions of hybrid monads originate from Renato Neves's PhD thesis.
The List Unfold monad
newtype ListUnfold a Source #
The List Unfold monad arises from free skewed algebras. It implements a form of nondeterminism similar to the usual list monad, but new choices may arise only in the last element (so the bind operation can only rename other elements), essentially unfolding a list. If new choices arise in the "init" of the list, the entire computation fails. Also, failure is always global. The join operation is defined as follows:
join xss | null xss = []
| any null xss = []
| any (not . isSingle) (init xss) = []
| otherwise = concat xss
For example:
>>>[1,1,1,4] >>= \x -> [1..x] :: ListUnfold IntListUnfold [1,1,1,1,2,3,4]>>>[1,2,1,4] >>= \x -> [1..x] :: ListUnfold IntListUnfold []>>>[1,0,1,4] >>= \x -> [1..x] :: ListUnfold IntListUnfold []
The Stutter monad
replicateLast :: Int -> [a] -> [a] Source #
Repeat the last element on the list n additional times, that is:
replicateLast n [] = [] replicateLast n xs = xs ++ replicate n (last xs)
newtype Stutter (n :: Nat) a Source #
The Stutter monad arises from free stutter algebras. Its join is
a concat of the longest prefix consisting only of singletons with a
"stutter" on the last singleton (that is, the last singleton is
additionally repeated n+1 times for an n fixed in the type). It
doesn't stutter only when the init consists only of singletons and
the last list is non-empty. The join can thus be defined as follows
(omitting the conversion of the type-level Nat n to a run-time
value):
join xss | null xss
= []
| any (not . isSingle) (init xss) || null (last xss)
= replicateLast (n + 1) (concat $ takeWhile isSingle (init xss))
| otherwise
= concat xss
The Stutter monad is quite similar to ListUnfold. The
difference is that when the latter fails (that is, its join results
in an empty list), the former stutters on the last singleton.
Examples:
>>>join ["1", "2", "buckle", "my", "shoe"] :: Stutter 5 CharStutter "12222222">>>join ["1", "2", "buckle"] :: Stutter 5 CharStutter "12buckle">>>join ["1", "2", "", "my", "shoe"] :: Stutter 5 CharStutter "12222222"
The Stutter-Keeper monad
newtype StutterKeeper (n :: Nat) a Source #
The stutter-keeper monad arises from free stutter-keeper
algebras. Its join stutters (as in the Stutter monad) if the
first non-singleton list in empty. Otherwise, it keeps the
singleton prefix, and keeps the first non-singleton list. The join
can thus be defined as follows (omitting the conversion of the
type-level Nat n to a run-time value):
join xss | null xss
= []
| null (head (dropWhile isSingle (init xss) ++ [last xss]))
= replicateLast (n + 1) (concat $ takeWhile isSingle (init xss))
| otherwise
= map head (takeWhile isSingle (init xss))
++ head (dropWhile isSingle (init xss) ++ [last xss])
Examples:
>>>join ["1", "2", "buckle", "my", "shoe"] :: StutterKeeper 5 CharStutterKeeper "12buckle">>>join ["1", "2", "buckle"] :: StutterKeeper 5 CharStutterKeeper "12buckle">>>join ["1", "2", "", "my", "shoe"] :: StutterKeeper 5 CharStutterKeeper "12222222"
The Stutter-Stutter monad
newtype StutterStutter (n :: Nat) (m :: Nat) a Source #
The stutter-stutter monad arises from free stutter-stutter
algebras. It is similar to StutterKeeper, but instead of keeping
the first non-singleton list, it stutters on its first element
(unless the first non-singleton list is also the last list, in
which case it is kept in the result). The join can thus be defined
as follows (omitting the conversion of the type-level nats to
run-time values):
join xss | null xss
= []
| null (head (dropWhile isSingle (init xss) ++ [last xss]))
= replicateLast (n + 1) (concat $ takeWhile isSingle (init xss))
| any (not . isSingle) (init xss) || null (last xss)
= concat (takeWhile isSingle (init xss))
++ replicate (m + 2) (head (head (dropWhile isSingle (init xss))))
| otherwise
= concat xss
Examples:
>>>join ["1", "2", "buckle", "my", "shoe"] :: StutterStutter 5 10 CharStutterStutter "12bbbbbbbbbbbb">>>join ["1", "2", "buckle"] :: StutterStutter 5 10 CharStutterStutter "12buckle">>>join ["1", "2", "", "my", "shoe"] :: StutterStutter 5 10 CharStutterStutter "12222222"
Other monads
While all list monads have presentations in terms of operations and equations, some require infinitely many operations. This section contains monads that are either known to require infinitely many operations, or those for which no finite presentation is known, but we don't know for sure that such a presentation doesn't exist.
The Mini monad
The Mini monad is the minimal list monad, meaning that its join fails (= results in an empty list) for all values except the ones that appear in the unit laws (i.e., a singleton or a list of singletons):
join xss | isSingle xss = concat xss
| all isSingle xss = concat xss
| otherwise = []
For example:
>>>join ["HelloThere"] :: Mini CharMini "HelloThere">>>join ["Hello", "There"] :: Mini CharMini ""
It does not arise from a subclass of PointedMagma (or any
algebraic theory with a finite number of operations for that
matter).
The Odd monad (?)
The join of the Odd monad is a concat of the inner lists provided there is an odd number of them, and that all of them are of odd length themselves. Otherwise (modulo cases needed for the unit laws), it returns an empty list.
join xss | isSingle xss = concat xss
| all isSingle xss = concat xss
| odd (length xss)
&& all (odd . length) xss = concat xss
| otherwise = []
For example:
>>>join ["Elvis", "Presley"] :: Odd CharOdd "">>>join ["Elvis", "Aaron", "Presley"] :: Odd CharOdd "ElvisAaronPresley">>>join ["Roy", "Kelton", "Orbison"] :: Odd CharOdd ""
At the moment, it is unclear whether it comes from a finite algebraic theory (or that it is indeed a monad).
The Short Stutter-Keeper monad (?)
newtype ShortStutterKeeper (n :: Nat) (p :: Nat) a Source #
This monad works just like the StutterKeeper monad but it takes
a prefix of the result of join of length p+2 (unless the unit
laws say otherwise). Thus, its join is defined as follows (omitting
the conversion of the type-level Nat p to a run-time value):
join xss | isSingle xss = concat xss
| all isSingle xss = concat xss
| otherwise = take (p + 2) $ toList
((Control.Monad.join $ StutterKeeper $ fmap StutterKeeper xss)
:: StutterKeeper n _)
For example:
>>>join ["1", "2", "buckle", "my", "shoe"] :: ShortStutterKeeper 5 2 CharShortStutterKeeper "12bu">>>join ["1", "2", "buckle"] :: ShortStutterKeeper 5 2 CharShortStutterKeeper "12bu">>>join ["1", "2", "", "my", "shoe"] :: ShortStutterKeeper 5 2 CharShortStutterKeeper "1222"
Compare the ShortFront monad
on non-empty lists.