serokell-util-0.8.0: General-purpose functions by Serokell

Safe HaskellNone
LanguageHaskell2010

Serokell.Util.Lens

Description

Extra operators on Lens

Synopsis

Documentation

(%%=) :: Lens' s a -> State a b -> State s b infix 4 Source #

Similar to %= operator, but takes State action instead of (a -> a)

(%?=) :: Lens' s a -> ExceptT t (State a) b -> ExceptT t (State s) b infix 4 Source #

Like %%= but with possiblity of failure

class Monad m => WrappedM m where Source #

Similar to Wrapped, but for Monads.

Associated Types

type UnwrappedM m :: * -> * Source #

Methods

_WrappedM :: Iso' (m a) (UnwrappedM m a) Source #

packM :: m a -> UnwrappedM m a Source #

unpackM :: UnwrappedM m a -> m a Source #

Instances

zoom' :: MonadState s m => LensLike' (Zoomed (State s) a) s t -> StateT t Identity a -> m a Source #

A zoom which works in arbitrary MonadState.

See https://github.com/ekmett/lens/issues/580. You might be surprised but actual zoom doesn't work in any MonadState, it only works in a handful of state monads and their combinations defined by Zoom.

magnify' :: MonadReader s m => LensLike' (Magnified (Reader s) a) s t -> ReaderT t Identity a -> m a Source #

A magnify which works in arbitrary MonadReader.

listL :: (IsList (t a), IsList (t b)) => Iso (t a) (t b) [Item (t a)] [Item (t b)] Source #

This isomorphism can be used to convert to or from an instance of IsList.

Note that this function is quite general but doesn't allow to switch container - in most cases such behavious eliminates need in specifing container type manually.