lgtk-0.2: lens-based GUI with Gtk backend

Safe HaskellSafe-Inferred

Data.MLens

Contents

Synopsis

Monadic lenses data type

newtype MLens m a b Source

Monadic lenses.

The following representations would be also good for (MLens m a b):

  • a -> m (Store b (m a))
  • forall f . Functor f => (b -> m (f (m b))) -> a -> m (f (m a))
  • (a -> m b, b -> a -> m a)

The last representation has no efficient composition operation (the set operation on composition of n lenses use O(n * n) get operations with the last representation).

Using lenses which do not fulfil the lens laws are safe, but one should take extra care when doing program transformations or reasoning about code with impure lenses.

The following law is a minimum, but some lenses (which do logging) do not fulfil this:

  • get-no-effect: (getL k a >> return ()) === (return ())

TODO: List laws, document which laws hold for each lenses.

Constructors

MLens (a -> m (b, b -> m a)) 

Instances

Monad m => Category (MLens m) 

Side-effect free lenses

type Lens a b = MLens Identity a bSource

Side-effect free lenses.

The following representations would be also good for (Lens a b):

  • forall m . Monad m => MLens m a b

Laws for pure monadic lenses:

  • set-get: (setL l b a >>= getL l) === (setL l b a >> return b)
  • get-set: (getL l a >>= b -> setL l b a) === (return a)
  • set-set: (setL l b a >>= setL l b') === (setL l b' a)

For example, fstLens and (fstLens . fstLens) fulfil these laws.

fromLens :: Monad m => Lens a b -> MLens m a bSource

toLens :: (forall m. Monad m => MLens m a b) -> Lens a bSource

Lens construction

lens :: Monad m => (a -> b) -> (b -> a -> a) -> MLens m a bSource

Lens operations

getL :: Monad m => MLens m a b -> a -> m bSource

setL :: Monad m => MLens m a b -> b -> a -> m aSource

modL :: Monad m => MLens m b a -> (a -> a) -> b -> m bSource

Lens transformations

(***) :: Monad m => MLens m a b -> MLens m c d -> MLens m (a, c) (b, d)Source

Tensor product

could be defined as

instance Monad m => Tensor (MLens m)

Tensor is defined in Control.Category.Product in the data-lens package.

mapMLens :: (Monad m, Monad n) => Morph m n -> MLens m a b -> MLens n a bSource

joinML :: Monad m => (a -> m (MLens m a b)) -> MLens m a bSource

joinLens :: Monad m => MLens m a (MLens m a b) -> MLens m a bSource

It would be possible to define a Monad instance for (MLens m a) too, but monad laws would not hold.

Pure lenses

unitLens :: Monad m => MLens m a ()Source

fstLens :: Monad m => MLens m (a, b) aSource

sndLens :: Monad m => MLens m (a, b) bSource

maybeLens :: Monad m => MLens m (Bool, a) (Maybe a)Source

listLens :: Monad m => MLens m (Bool, (a, [a])) [a]Source

ithLens :: Monad m => Int -> MLens m [a] aSource

ithLens is pure only with proper preconditions.

Impure lenses

forkLens :: (Monoid a, Monad m) => MLens m a (a, a)Source

justLens :: Monad m => a -> MLens m (Maybe a) aSource

Auxiliary definitions

type Morph m n = forall a. m a -> n aSource