monad-coroutine-0.7: Coroutine monad transformer for suspending and resuming monadic computations

Data.Functor.Contravariant.Ticker

Contents

Description

This module defines the Ticker cofunctor, useful for 'ticking off' a prefix of the input.

Synopsis

The Ticker type

newtype Ticker x Source

This is a contra-functor data type for selecting a prefix of an input stream. If the next input item is acceptable, the ticker function returns the ticker for the rest of the stream. If not, it returns Nothing.

Constructors

Ticker (x -> Maybe (Ticker x)) 

Using a Ticker

splitTicked :: Ticker x -> [x] -> (Ticker x, [x], [x])Source

Extracts a list prefix accepted by the Ticker argument. Returns the modified ticker, the prefix, and the remainder of the list.

class Contravariant f where

Any instance should be subject to the following laws:

 contramap id = id
 contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Methods

contramap :: (a -> b) -> f b -> f a

Instances

Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input to each input to the comparison function.

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Contravariant Ticker 
Contravariant (Const a)

Control.Applicative.Const

Contravariant (Op a) 
Contravariant (Constant a)

Data.Functor.Constant

(Contravariant f, Contravariant g) => Contravariant (Product f g)

Data.Functor.Product

Ticker constructors

tickNone :: Ticker xSource

A ticker that accepts no input.

tickOne :: Ticker xSource

A ticker that accepts a single input item.

tickCount :: Int -> Ticker xSource

A ticker that accepts a given number of input items.

tickPrefixOf :: Eq x => [x] -> Ticker xSource

A ticker that accepts the longest prefix of input that matches a prefix of the argument list.

tickWhilePrefixOf :: [x -> Bool] -> Ticker xSource

A ticker that accepts a prefix of input as long as each item satisfies the predicate at the same position in the argument list. The length of the predicate list thus determines the maximum number of acepted values.

tickWhile :: (x -> Bool) -> Ticker xSource

A ticker that accepts all input as long as it matches the given predicate.

tickUntil :: (x -> Bool) -> Ticker xSource

A ticker that accepts all input items until one matches the given predicate.

tickAll :: Ticker xSource

A ticker that accepts all input.

Ticker combinators

andThen :: Ticker x -> Ticker x -> Ticker xSource

Sequential concatenation ticker combinator: when the first argument ticker stops ticking, the second takes over.

and :: Ticker x -> Ticker x -> Ticker xSource

Parallel conjunction ticker combinator: the result keeps ticking as long as both arguments do.

or :: Ticker x -> Ticker x -> Ticker xSource

Parallel choice ticker combinator: the result keeps ticking as long as any of the arguments does.