raaz-0.2.0: The raaz cryptographic library.

Safe HaskellSafe
LanguageHaskell2010

Raaz.Core.MonoidalAction

Contents

Description

A module that abstracts out monoidal actions.

Synopsis

Monoidal action

Consider any instance l of a length unit as a monoid under addition. Length units acts on pointers by displacing them. It turns out that this action is crucial in abstracting out many pointer manipulations in our library. In particular, Applicative parsers, memory allocators and data serialisers can be abstractly captured using this action.

We start with setting up some terminology. Our setting here is a space of points (captured by the type space) on which a monoid (captured by the type m) acts. The space which we are most interested in is the space of CryptoPtr and the monoid that act on it can be any instance of LengthUnit as described above.

In this module, we consider left actions of monoids, although right actions can be analogously defined as well. For applications we have in mind, namely for parsers etc, it is sufficient to restrict our attention to left actions. The left action will be written in multiplicative notation with the operator <.> being the multiplication.

class Monoid m => LAction m space where Source #

A monoid m acting on the left of a space. Think of a left action as a multiplication with the monoid. It should satisfy the law:

1 <.> p = p                         -- identity
a <> b <.> p  = a <.> b <.> p   -- successive displacements

Minimal complete definition

(<.>)

Methods

(<.>) :: m -> space -> space infixr 5 Source #

Instances

LengthUnit u => LAction u Pointer Source #

The most interesting monoidal action for us.

Methods

(<.>) :: u -> Pointer -> Pointer Source #

class (LAction m space, Monoid space) => Distributive m space Source #

A left-monoid action on a monoidal-space, i.e. the space on which the monoid acts is itself a monoid, is distributive if it satisfies the law:

a <.> p <> q  = (a <.> p) <> (a <.> q).

The above law implies that every element m is a monoid homomorphism.

data SemiR space m Source #

The semidirect product Space ⋊ Monoid. For monoids acting on monoidal spaces distributively the semi-direct product is itself a monoid. It turns out that data serialisers can essentially seen as a semidirect product.

Constructors

SemiR space !m 

Instances

Distributive m space => Monoid (SemiR space m) Source # 

Methods

mempty :: SemiR space m #

mappend :: SemiR space m -> SemiR space m -> SemiR space m #

mconcat :: [SemiR space m] -> SemiR space m #

(<++>) :: Monoid m => m -> m -> m infixr 5 Source #

An alternate symbol for <> more useful in the additive context.

semiRSpace :: SemiR space m -> space Source #

From the an element of semi-direct product Space ⋊ Monoid return the point.

semiRMonoid :: SemiR space m -> m Source #

From the an element of semi-direct product Space ⋊ Monoid return the monoid element.

Monoidal action on functors

class (Monoid m, Functor f) => LActionF m f where Source #

Uniform action of a monoid on a functor. The laws that should be satisfied are:

1 <<.>> fx  = fx
(a <> b) <<.>> fx  = a . (b <<.>> fx)
m <<.>> fmap f u = fmap f (m <<.>> u)   -- acts uniformly

Minimal complete definition

(<<.>>)

Methods

(<<.>>) :: m -> f a -> f a infixr 5 Source #

Instances

(Arrow arrow, LAction m space) => LActionF m (WrappedArrow arrow space) Source #

The action on the space translates to the action on field.

Methods

(<<.>>) :: m -> WrappedArrow arrow space a -> WrappedArrow arrow space a Source #

class (Applicative f, LActionF m f) => DistributiveF m f Source #

The generalisation of distributivity to applicative functors. This generalisation is what allows us to capture applicative functors like parsers. For an applicative functor, and a monoid acting uniformly on it, we say that the action is distributive if the following laws are satisfied:

m <<.>> (pure a) = pure a            -- pure values are stoic
m <<.>> (a <*> b) = (m <<.>> a) <*> (m <<.>> b)  -- dist

Instances

(Arrow arrow, LAction m space) => DistributiveF m (WrappedArrow arrow space) Source # 

data TwistRF f m a Source #

The twisted functor is essentially a generalisation of semi-direct product to applicative functors.

Constructors

TwistRF (f a) !m 

Instances

Functor f => Functor (TwistRF f m) Source # 

Methods

fmap :: (a -> b) -> TwistRF f m a -> TwistRF f m b #

(<$) :: a -> TwistRF f m b -> TwistRF f m a #

DistributiveF m f => Applicative (TwistRF f m) Source # 

Methods

pure :: a -> TwistRF f m a #

(<*>) :: TwistRF f m (a -> b) -> TwistRF f m a -> TwistRF f m b #

(*>) :: TwistRF f m a -> TwistRF f m b -> TwistRF f m b #

(<*) :: TwistRF f m a -> TwistRF f m b -> TwistRF f m a #

twistFunctorValue :: TwistRF f m a -> f a Source #

Get the underlying functor value.

twistMonoidValue :: TwistRF f m a -> m Source #

Get the underlying monoid value.

Fields

The main goal behind looking at monoidal actions are to captures concrete objects of interest to us like parsers, serialisers and memory allocators. These are essentially functions with domain CryptoPtr. For example, a parser is a function that takes a CryptoPtr, reads n bytes say and produces a result a. To sequence the next parse we need to essentially keep track of this n. If we abstract this out to the general setting we need to consider functions whose domain is the space of points. We use the physicist's terminology and call them fields. The action of the monoid on a space of points naturally extends to fields on them

F^g   = λ x -> F (x^g)

For our applications, we need to define generalised fields associated with arrows. This is because we often have to deal with functions that have side effects (i.e. Kleisli arrows). However, for conceptual understanding, it is sufficient to stick to ordinary functions. In fact, the informal proofs that we have scattered in the source all have been written only for the arrow ->.

type FieldA arrow = WrappedArrow arrow Source #

A field on the space is a function from the points in the space to some value. Here we define it for a general arrow.

type FieldM monad = FieldA (Kleisli monad) Source #

A monadic arrow field.

type Field = FieldA (->) Source #

A field where the underlying arrow is the (->). This is normally what we call a field.

computeField :: Field space b -> space -> b Source #

Compute the value of a field at a given point in the space.

runFieldM :: FieldM monad space b -> space -> monad b Source #

Runs a monadic field at a given point in the space.

liftToFieldM :: (a -> m b) -> FieldM m a b Source #

Lift a monadic action to FieldM.