lens-4.13.1: Lenses, Folds and Traversals

Copyright(C) 2012-16 Edward Kmett, Michael Sloan
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <[email protected]>
Stabilityexperimental
PortabilityRank2, MPTCs, fundeps
Safe HaskellTrustworthy
LanguageHaskell98

Control.Lens.Wrapped

Contents

Description

The Wrapped class provides similar functionality as Control.Newtype, from the newtype package, but in a more convenient and efficient form.

There are a few functions from newtype that are not provided here, because they can be done with the Iso directly:

Control.Newtype.over Sum f ≡ _Unwrapping Sum %~ f
Control.Newtype.under Sum f ≡ _Wrapping Sum %~ f
Control.Newtype.overF Sum f ≡ mapping (_Unwrapping Sum) %~ f
Control.Newtype.underF Sum f ≡ mapping (_Wrapping Sum) %~ f

under can also be used with _Unwrapping to provide the equivalent of Control.Newtype.under. Also, most use cases don't need full polymorphism, so only the single constructor _Wrapping functions would be needed.

These equivalences aren't 100% honest, because newtype's operators need to rely on two Newtype constraints. This means that the wrapper used for the output is not necessarily the same as the input.

Synopsis

Wrapping and Unwrapping monomorphically

class Wrapped s where Source

Wrapped provides isomorphisms to wrap and unwrap newtypes or data types with one constructor.

Minimal complete definition

Nothing

Associated Types

type Unwrapped s :: * Source

Methods

_Wrapped' :: Iso' s (Unwrapped s) Source

An isomorphism between s and a.

Instances

Wrapped PatternMatchFail Source 
Wrapped RecSelError Source 
Wrapped RecConError Source 
Wrapped RecUpdError Source 
Wrapped NoMethodError Source 
Wrapped AssertionFailed Source 
Wrapped ErrorCall Source 
Wrapped All Source 
Wrapped Any Source 
Wrapped IntSet Source 
Wrapped (Identity a) Source 
Wrapped (ZipList a) Source 
Wrapped (Dual a) Source 
Wrapped (Endo a) Source 
Wrapped (Sum a) Source 
Wrapped (Product a) Source 
Wrapped (First a) Source 
Wrapped (Last a) Source 
Wrapped (Down a) Source 
Wrapped (IntMap a) Source 
Ord a => Wrapped (Set a) Source 
Wrapped (Seq a) Source 
Wrapped (Predicate a) Source 
Wrapped (Comparison a) Source 
Wrapped (Equivalence a) Source 
Wrapped (Min a) Source 
Wrapped (Max a) Source 
Wrapped (First a) Source 
Wrapped (Last a) Source 
Wrapped (WrappedMonoid a) Source 
Wrapped (Option a) Source 
Wrapped (NonEmpty a) Source 
(Hashable a, Eq a) => Wrapped (HashSet a) Source 
Wrapped (Vector a) Source 
Unbox a => Wrapped (Vector a) Source 
Storable a => Wrapped (Vector a) Source 
Prim a => Wrapped (Vector a) Source 
Wrapped (Op a b) Source 
Wrapped (Const a x) Source 
Wrapped (WrappedMonad m a) Source 
Wrapped (ArrowMonad m a) Source 
Wrapped (IdentityT m a) Source 
Ord k => Wrapped (Map k a) Source 
Wrapped (ListT m a) Source 
Wrapped (Reverse f a) Source 
Wrapped (Backwards f a) Source 
Wrapped (MaybeT m a) Source 
Wrapped (Constant a b) Source 
(Hashable k, Eq k) => Wrapped (HashMap k a) Source 
Wrapped (WrappedArrow a b c) Source 
Wrapped (Kleisli m a b) Source 
Wrapped (Alt k f a) Source 
Wrapped (TracedT m w a) Source 
Wrapped (Compose f g a) Source 
Wrapped (ComposeFC f g a) Source 
Wrapped (ComposeCF f g a) Source 
Wrapped (ContT r m a) Source 
Wrapped (ReaderT r m a) Source 
Wrapped (StateT s m a) Source 
Wrapped (StateT s m a) Source 
Wrapped (ErrorT e m a) Source 
Wrapped (WriterT w m a) Source 
Wrapped (WriterT w m a) Source 
Wrapped (Compose f g a) Source 
Wrapped (Tagged k s a) Source 
Wrapped (RWST r w s m a) Source 
Wrapped (RWST r w s m a) Source 

_Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s) Source

This is a convenient version of _Wrapped with an argument that's ignored.

The user supplied function is ignored, merely its type is used.

_Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s Source

This is a convenient version of _Wrapped with an argument that's ignored.

The user supplied function is ignored, merely its type is used.

Wrapping and unwrapping polymorphically

class Wrapped s => Rewrapped s t Source

Instances

(~) * t PatternMatchFail => Rewrapped PatternMatchFail t Source 
(~) * t RecSelError => Rewrapped RecSelError t Source 
(~) * t RecConError => Rewrapped RecConError t Source 
(~) * t RecUpdError => Rewrapped RecUpdError t Source 
(~) * t NoMethodError => Rewrapped NoMethodError t Source 
(~) * t AssertionFailed => Rewrapped AssertionFailed t Source 
(~) * t ErrorCall => Rewrapped ErrorCall t Source 
(~) * t All => Rewrapped All t Source 
(~) * t Any => Rewrapped Any t Source 
(~) * t IntSet => Rewrapped IntSet t Source

Use wrapping fromList. unwrapping returns a sorted list.

(~) * t (Identity b) => Rewrapped (Identity a) t Source 
(~) * t (ZipList b) => Rewrapped (ZipList a) t Source 
(~) * t (Dual b) => Rewrapped (Dual a) t Source 
(~) * t (Endo b) => Rewrapped (Endo b) t Source 
(~) * t (Sum b) => Rewrapped (Sum a) t Source 
(~) * t (Product b) => Rewrapped (Product a) t Source 
(~) * t (First b) => Rewrapped (First a) t Source 
(~) * t (Last b) => Rewrapped (Last a) t Source 
(~) * t (Down a) => Rewrapped (Down a) t Source 
(~) * t (IntMap a') => Rewrapped (IntMap a) t Source

Use wrapping fromList. unwrapping returns a sorted list.

((~) * t (Set a'), Ord a) => Rewrapped (Set a) t Source

Use wrapping fromList. unwrapping returns a sorted list.

(~) * t (Seq a') => Rewrapped (Seq a) t Source 
(~) * t (Predicate b) => Rewrapped (Predicate a) t Source 
(~) * t (Comparison b) => Rewrapped (Comparison a) t Source 
(~) * t (Equivalence b) => Rewrapped (Equivalence a) t Source 
(~) * t (Min b) => Rewrapped (Min a) t Source 
(~) * t (Max b) => Rewrapped (Max a) t Source 
(~) * t (First b) => Rewrapped (First a) t Source 
(~) * t (Last b) => Rewrapped (Last a) t Source 
(~) * t (WrappedMonoid b) => Rewrapped (WrappedMonoid a) t Source 
(~) * t (Option b) => Rewrapped (Option a) t Source 
(~) * t (NonEmpty b) => Rewrapped (NonEmpty a) t Source 
((~) * t (HashSet a'), Hashable a, Eq a) => Rewrapped (HashSet a) t Source

Use wrapping fromList. Unwrapping returns some permutation of the list.

(~) * t (Vector a') => Rewrapped (Vector a) t Source 
(Unbox a, (~) * t (Vector a')) => Rewrapped (Vector a) t Source 
(Storable a, (~) * t (Vector a')) => Rewrapped (Vector a) t Source 
(Prim a, (~) * t (Vector a')) => Rewrapped (Vector a) t Source 
(~) * t (Op a' b') => Rewrapped (Op a b) t Source 
(~) * t (Const a' x') => Rewrapped (Const a x) t Source 
(~) * t (WrappedMonad m' a') => Rewrapped (WrappedMonad m a) t Source 
(~) * t (ArrowMonad m' a') => Rewrapped (ArrowMonad m a) t Source 
(~) * t (IdentityT n b) => Rewrapped (IdentityT m a) t Source 
((~) * t (Map k' a'), Ord k) => Rewrapped (Map k a) t Source

Use wrapping fromList. unwrapping returns a sorted list.

(~) * t (ListT n b) => Rewrapped (ListT m a) t Source 
(~) * t (Reverse g b) => Rewrapped (Reverse f a) t Source 
(~) * t (Backwards g b) => Rewrapped (Backwards f a) t Source 
(~) * t (MaybeT n b) => Rewrapped (MaybeT m a) t Source 
(~) * t (Constant a' b') => Rewrapped (Constant a b) t Source 
((~) * t (HashMap k' a'), Hashable k, Eq k) => Rewrapped (HashMap k a) t Source

Use wrapping fromList. Unwrapping returns some permutation of the list.

(~) * t (WrappedArrow a' b' c') => Rewrapped (WrappedArrow a b c) t Source 
(~) * t (Kleisli m' a' b') => Rewrapped (Kleisli m a b) t Source 
(~) * t (Alt k g b) => Rewrapped (Alt k f a) t Source 
(~) * t (TracedT m' w' a') => Rewrapped (TracedT m w a) t Source 
(~) * t (Compose f' g' a') => Rewrapped (Compose f g a) t Source 
(~) * t (ComposeFC f' g' a') => Rewrapped (ComposeFC f g a) t Source 
(~) * t (ComposeCF f' g' a') => Rewrapped (ComposeCF f g a) t Source 
(~) * t (ContT r' m' a') => Rewrapped (ContT r m a) t Source 
(~) * t (ReaderT r n b) => Rewrapped (ReaderT r m a) t Source 
(~) * t (StateT s' m' a') => Rewrapped (StateT s m a) t Source 
(~) * t (StateT s' m' a') => Rewrapped (StateT s m a) t Source 
(~) * t (ErrorT e' m' a') => Rewrapped (ErrorT e m a) t Source 
(~) * t (WriterT w' m' a') => Rewrapped (WriterT w m a) t Source 
(~) * t (WriterT w' m' a') => Rewrapped (WriterT w m a) t Source 
(~) * t (Compose f' g' a') => Rewrapped (Compose f g a) t Source 
(~) * t (Tagged k s' a') => Rewrapped (Tagged k s a) t Source 
(~) * t (RWST r' w' s' m' a') => Rewrapped (RWST r w s m a) t Source 
(~) * t (RWST r' w' s' m' a') => Rewrapped (RWST r w s m a) t Source 

class (Rewrapped s t, Rewrapped t s) => Rewrapping s t Source

Instances

(Rewrapped s t, Rewrapped t s) => Rewrapping s t Source 

_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) Source

Work under a newtype wrapper.

>>> Const "hello" & _Wrapped %~ Prelude.length & getConst
5
_Wrappedfrom _Unwrapped
_Unwrappedfrom _Wrapped

_Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t) Source

This is a convenient version of _Wrapped with an argument that's ignored.

The user supplied function is ignored, merely its types are used.

_Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s Source

This is a convenient version of _Unwrapped with an argument that's ignored.

The user supplied function is ignored, merely its types are used.

Operations

op :: Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s Source

Given the constructor for a Wrapped type, return a deconstructor that is its inverse.

Assuming the Wrapped instance is legal, these laws hold:

op f . f ≡ id
f . op f ≡ id
>>> op Identity (Identity 4)
4
>>> op Const (Const "hello")
"hello"

ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s) Source

This combinator is based on ala from Conor McBride's work on Epigram.

As with _Wrapping, the user supplied function for the newtype is ignored.

>>> ala Sum foldMap [1,2,3,4]
10
>>> ala All foldMap [True,True]
True
>>> ala All foldMap [True,False]
False
>>> ala Any foldMap [False,False]
False
>>> ala Any foldMap [True,False]
True
>>> ala Sum foldMap [1,2,3,4]
10
>>> ala Product foldMap [1,2,3,4]
24

You may want to think of this combinator as having the following, simpler, type.

ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped s

alaf :: (Functor f, Functor g, Rewrapping s t) => (Unwrapped s -> s) -> (f t -> g s) -> f (Unwrapped t) -> g (Unwrapped s) Source

This combinator is based on ala' from Conor McBride's work on Epigram.

As with _Wrapping, the user supplied function for the newtype is ignored.

alaf :: Rewrapping s t => (Unwrapped s -> s) -> ((r ->  t) -> e -> s) -> (r -> Unwrapped t) -> e -> Unwrapped s
>>> alaf Sum foldMap Prelude.length ["hello","world"]
10

Pattern Synonyms

pattern Wrapped :: () => Rewrapped s s => Unwrapped s -> s Source

pattern Unwrapped :: () => (MonadReader (Unwrapped t) ((->) (Unwrapped t)), Rewrapped t t) => t -> Unwrapped t Source