ReplicateEffects-0.3: Composable replication schemes of applicative functors

Safe HaskellSafe-Inferred

Control.Replicate

Contents

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, between 3 5 <|> between 4 6 is equivalent to between 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.

Synopsis

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 Replicate is both Applicative and Category, it is also an Arrow.

ArrowZero Replicate

Behaves exactly as the Alternative instance.

ArrowPlus Replicate

Behaves exactly as the Alternative instance.

Category Replicate

Pairwise multiplication.

id is the singleton set of exactly one occurrence {1}. It is synonymous with one.

. produces the set of occurrences that are the products of all possible pairs from the two operands.

Functor (Replicate a)

Map over the composite result type.

Functor (Replicate a) => Applicative (Replicate a)

Pairwise addition.

pure is the singleton set of exactly zero occurrences {0}. It is synonymous with zero.

<*> produces the set of occurrences that are the sums of all possible pairs from the two operands.

An example: sequencing exactly 2 {2} with exactly 3 {3} produces {2+3} = {5}.

Another example: sequencing the set {0, 1} (opt) with itself produces {0+0, 0+1, 1+0, 1+1} = {0, 1, 1, 2} = {0, 1, 2}. In case of overlap, like in this example, <*> favors the heads (of type Maybe b) from the left operand.

Applicative (Replicate a) => Alternative (Replicate a)

empty is the empty set {} of allowed occurrences. Not even performing an action zero times is allowed in that case.

<|> computes the union of the two sets. For example, between 2 4 <|> between 3 5 is equivalent to between 2 5. Again, in case of overlap, head values from the left operand are favored.

Monoid (Replicate a b)

Behaves exactly as the Alternative instance.

(*!) :: 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

Run an action a certain number of times, using <|> to branch (at the deepest point possible) if multiple frequencies are allowed. Use lazy choices: always make the pure alternative the left operand of <|>.

sizes :: Replicate a b -> [Int]Source

Enumerate all the numbers of allowed occurrences encoded by the replication scheme.

Common replication schemes

zero :: b -> Replicate a bSource

Perform an action exactly zero times.

one :: Replicate a aSource

Perform an action exactly one time.

two :: Replicate a (a, a)Source

Perform an action exactly two times.

three :: Replicate a (a, a, a)Source

Perform an action exactly three times.

opt :: Replicate a (Maybe a)Source

Perform an action zero or one times.

many :: Replicate a [a]Source

Perform an action zero or more times.

some :: Replicate a [a]Source

Perform an action one or more times.

exactly :: Int -> Replicate a [a]Source

Perform an action exactly so many times.

atLeast :: Int -> Replicate a [a]Source

Perform an action at least so many times.

atMost :: Int -> Replicate a [a]Source

Perform an action at most so many times.

between :: Int -> Int -> Replicate a [a]Source

Allow an action to be performed between so and so many times (inclusive).

forever :: Replicate a bSource

Repeat an action forever.