Agda-2.6.4.3: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Utils.Lens

Description

A cut-down implementation of lenses, with names taken from Edward Kmett's lens package.

Synopsis

Documentation

type Lens' o i = forall f. Functor f => (i -> f i) -> o -> f o Source #

Van Laarhoven style homogeneous lenses. Mnemoic: "Lens outer inner", same type argument order as 'get :: o -> i'.

type LensGet o i = o -> i Source #

type LensSet o i = i -> o -> o Source #

type LensMap o i = (i -> i) -> o -> o Source #

key :: Ord k => k -> Lens' (Map k v) (Maybe v) Source #

Access a map value at a given key.

(.=) :: MonadState o m => Lens' o i -> i -> m () infix 4 Source #

Write a part of the state.

over :: Lens' o i -> LensMap o i Source #

Modify inner part i of structure o using a function i -> i.

set :: Lens' o i -> LensSet o i Source #

Set inner part i of structure o as designated by Lens' o i.

(^.) :: o -> Lens' o i -> i infixl 8 Source #

Get inner part i of structure o as designated by Lens' o i.

lFst :: Lens' (a, b) a Source #

lSnd :: Lens' (a, b) b Source #

focus :: Monad m => Lens' o i -> StateT i m a -> StateT o m a Source #

Focus on a part of the state for a stateful computation.

use :: MonadState o m => Lens' o i -> m i Source #

Read a part of the state.

(%=) :: MonadState o m => Lens' o i -> (i -> i) -> m () infix 4 Source #

Modify a part of the state.

(%==) :: MonadState o m => Lens' o i -> (i -> m i) -> m () infix 4 Source #

Modify a part of the state monadically.

(%%=) :: MonadState o m => Lens' o i -> (i -> m (i, r)) -> m r infix 4 Source #

Modify a part of the state monadically, and return some result.

locallyState :: MonadState o m => Lens' o i -> (i -> i) -> m r -> m r Source #

Modify a part of the state locally.

view :: MonadReader o m => Lens' o i -> m i Source #

Ask for part of read-only state.

locally :: MonadReader o m => Lens' o i -> (i -> i) -> m a -> m a Source #

Modify a part of the state in a subcomputation.

locally' :: ((o -> o) -> m a -> m a) -> Lens' o i -> (i -> i) -> m a -> m a Source #

contains :: Ord k => k -> Lens' (Set k) Bool Source #

Focus on given element in a set.

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 #

Flipped version of <$>.

(<&>) = flip fmap

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

Since: base-4.11.0.0