Safe Haskell | Safe-Inferred |
---|
Control.Replicate
Description
Composable replication schemes of applicative actions.
This module separates common combinators such as some
and many
(from
Control.Applicative
) from any actual applicative actions. It offers
composable building blocks for expressing the number (or numbers) of times
an action should be executed. The building blocks themselves are composed
using the standard Applicative
, Alternative
and Category
combinators.
Replication schemes can then be run with *!
and *?
to produce actual
actions.
Some examples help see how this works. One of the simplest schemes is
one
:
one :: Replicate a a
one *! p
is equivalent to just p
.
Schemes can be summed by composing them in applicative fashion. In the following example, the resulting tuple type makes it clear that the action has been run twice and no information is lost:
two :: Replicate a (a, a) two = (,) <$> one <*> one
two *! p
is equivalent to (,) <$> p <*> p
.
Things get more interesting if we use the choice combinator <|>
to form
the union of two schemes.
oneOrTwo :: Replicate a (Either a (a, a)) oneOrTwo = Left <$> one <|> Right <$> two
Running schemes that allow multiple frequencies expand to actions that
always use <|>
as late as possible. Since oneOrTwo
runs an action at
least once, we can start by running the action once immediately and
only then choose whether we want to stop there or run it a second time.
Running it with *!
expands to:
\p -> p <**> ( -- Either run the action again and yield Right ... (\y x -> Right (x, y)) <$> p <|> -- ... or stop here and yield Left. pure Left )
Replication schemes can be thought of as sets of Peano numerals. If there
is overlap between the two operands to <|>
, the overlap collapses and
is lost in the result. For example,
is
equivalent to between
3 5 <|> between 4 6between 3 6
, a scheme that runs an action 3, 4, 5 or 6
times.
The example above made the second p
the first choice and the pure
option the second choice to <|>
. In some cases the other way around is
preferred. This is what *?
is for; it prefers running an action fewer
times over more times. Running oneOrTwo
with it is equivalent to:
\p -> p <**> ( -- Either stop here and yield Left ... pure Left <|> -- ... or run the action again and yield Right. (\y x -> Right (x, y)) <$> p )
Finally, schemes can be multiplied by composing them with the dot operator
.
from Control.Category
.
twiceThree :: Replicate a ((a, a, a), (a, a, a)) twiceThree = two . three thriceTwo :: Replicate a ((a, a), (a, a), (a, a)) thriceTwo = three . two
If .
's operands allow multiple frequencies, the result will allow the
products of all pairs of frequencies from the operands. We can use this to
e.g. produce all even numbers of occurrences:
even :: Replicate a [(a, a)] even = many . two
In this example many
behaves like the standard Applicative many
,
allowing an action to be run any number of {0, 1, ..} times.
- data Replicate a b where
- (*!) :: Alternative f => Replicate a b -> f a -> f b
- (*?) :: Alternative f => Replicate a b -> f a -> f b
- sizes :: Replicate a b -> [Int]
- zero :: b -> Replicate a b
- one :: Replicate a a
- two :: Replicate a (a, a)
- three :: Replicate a (a, a, a)
- opt :: Replicate a (Maybe a)
- many :: Replicate a [a]
- some :: Replicate a [a]
- exactly :: Int -> Replicate a [a]
- atLeast :: Int -> Replicate a [a]
- atMost :: Int -> Replicate a [a]
- between :: Int -> Int -> Replicate a [a]
- forever :: Replicate a b
Type constructor Replicate
data Replicate a b whereSource
A set of frequencies which with an applicative action is allowed to
occur. a
is the result type of a single atomic action. b
is the
composite result type after executing the action a number of times allowed
by this set.
Constructors
Nil :: Replicate a b | |
Cons :: (c -> b) -> Maybe c -> Replicate a (a -> c) -> Replicate a b |
Instances
Arrow Replicate | As |
ArrowZero Replicate | Behaves exactly as the |
ArrowPlus Replicate | Behaves exactly as the |
Category Replicate | Pairwise multiplication.
|
Functor (Replicate a) | Map over the composite result type. |
Functor (Replicate a) => Applicative (Replicate a) | Pairwise addition.
An example: sequencing Another example: sequencing the set {0, 1} ( |
Applicative (Replicate a) => Alternative (Replicate a) |
|
Monoid (Replicate a b) | Behaves exactly as the |
(*!) :: Alternative f => Replicate a b -> f a -> f bSource
Run an action a certain number of times, using <|>
to branch (at the
deepest point possible) if multiple frequencies are allowed. Use greedy
choices: always make the longer alternative the left operand of <|>
.
(*?) :: Alternative f => Replicate a b -> f a -> f bSource
sizes :: Replicate a b -> [Int]Source
Enumerate all the numbers of allowed occurrences encoded by the replication scheme.