| Portability | Rank2, MPTCs, fundeps | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Trustworthy | 
Control.Lens.Wrapped
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.overSumf ≡wrappingSum%~f Control.Newtype.underSumf ≡unwrappingSum%~f Control.Newtype.overFSumf ≡mapping(wrappingSum)%~f Control.Newtype.underFSumf ≡mapping(unwrappingSum)%~f
under can also be used with wrapping 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.
- class Wrapped s t a b | a -> s, b -> t, a t -> s, b s -> t where
- unwrapped :: Wrapped t s b a => Iso a b s t
- wrapped' :: Wrapped s s a a => Iso' s a
- unwrapped' :: Wrapped s s a a => Iso' a s
- wrapping :: Wrapped s s a a => (s -> a) -> Iso s s a a
- unwrapping :: Wrapped s s a a => (s -> a) -> Iso a a s s
- wrappings :: Wrapped s t a b => (s -> a) -> (t -> b) -> Iso s t a b
- unwrappings :: Wrapped t s b a => (s -> a) -> (t -> b) -> Iso a b s t
- op :: Wrapped s s a a => (s -> a) -> a -> s
- ala :: Wrapped s s a a => (s -> a) -> ((s -> a) -> e -> a) -> e -> s
- alaf :: Wrapped s s a a => (s -> a) -> ((r -> a) -> e -> a) -> (r -> s) -> e -> s
Documentation
class Wrapped s t a b | a -> s, b -> t, a t -> s, b s -> t whereSource
Wrapped provides isomorphisms to wrap and unwrap newtypes or
 data types with one constructor.
Methods
An isomorphism between s and a and a related one between t and b, such that when a = b, s = t.
This is often used via wrapping to aid type inference.
Instances
| Wrapped Bool Bool All All | |
| Wrapped Bool Bool Any Any | |
| Wrapped String String PatternMatchFail PatternMatchFail | |
| Wrapped String String RecSelError RecSelError | |
| Wrapped String String RecConError RecConError | |
| Wrapped String String RecUpdError RecUpdError | |
| Wrapped String String NoMethodError NoMethodError | |
| Wrapped String String AssertionFailed AssertionFailed | |
| Wrapped String String ErrorCall ErrorCall | |
| Wrapped a a' (Identity a) (Identity a') | |
| Wrapped a b (Dual a) (Dual b) | |
| Wrapped a b (Product a) (Product b) | |
| Wrapped a b (Sum a) (Sum b) | |
| Wrapped a a' (Constant a b) (Constant a' b') | |
| Wrapped a b (Reviewed s a) (Reviewed t b) | |
| Wrapped a b (Const a x) (Const b y) | |
| Wrapped a b (Tagged k s a) (Tagged k1 t b) | |
| Wrapped [Int] [Int] IntSet IntSet | |
| Wrapped [(Int, a)] [(Int, b)] (IntMap a) (IntMap b) | |
| Wrapped [a] [b] (Seq a) (Seq b) | |
| (Ord a, Ord b) => Wrapped [a] [b] (Set a) (Set b) | |
| (Hashable a, Eq a, Hashable b, Eq b) => Wrapped [a] [b] (HashSet a) (HashSet b) | Use  | 
| Wrapped [a] [b] (ZipList a) (ZipList b) | |
| Wrapped (Maybe a) (Maybe b) (Last a) (Last b) | |
| Wrapped (Maybe a) (Maybe b) (First a) (First b) | |
| (Ord k, Ord k') => Wrapped [(k, a)] [(k', b)] (Map k a) (Map k' b) | |
| (Hashable k, Eq k, Hashable k', Eq k') => Wrapped [(k, a)] [(k', b)] (HashMap k a) (HashMap k' b) | Use  | 
| Wrapped (f a) (f' a') (Reverse f a) (Reverse f' a') | |
| Wrapped (m (Maybe a)) (m' (Maybe a')) (MaybeT m a) (MaybeT m' a') | |
| Wrapped (m [a]) (m' [a']) (ListT m a) (ListT m' a') | |
| Wrapped (m a) (m' a') (IdentityT m a) (IdentityT m' a') | |
| Wrapped (f a) (f' a') (Backwards f a) (Backwards f' a') | |
| Wrapped (m a) (n b) (WrappedMonad m a) (WrappedMonad n b) | |
| Wrapped (f (g a)) (f' (g' a')) (ComposeCF f g a) (ComposeFC f' g' a') | |
| Wrapped (f (g a)) (f' (g' a')) (ComposeFC f g a) (ComposeFC f' g' a') | |
| Wrapped (f (g a)) (f' (g' a')) (Compose f g a) (Compose f' g' a') | |
| Wrapped (w (m -> a)) (w' (m' -> a')) (TracedT m w a) (TracedT m' w' a') | |
| Wrapped (m (a, w)) (m' (a', w')) (WriterT w m a) (WriterT w' m' a') | |
| Wrapped (m (a, w)) (m' (a', w')) (WriterT w m a) (WriterT w' m' a') | |
| Wrapped (m (Either e a)) (m' (Either e' a')) (ErrorT e m a) (ErrorT e' m' a') | |
| Wrapped (f (g a)) (f' (g' a')) (Compose f g a) (Compose f' g' a') | |
| Wrapped (a -> a -> Bool) (a' -> a' -> Bool) (Equivalence a) (Equivalence a') | |
| Wrapped (a -> a -> Ordering) (a' -> a' -> Ordering) (Comparison a) (Comparison a') | |
| Wrapped (a -> Bool) (a' -> Bool) (Predicate a) (Predicate a') | |
| Wrapped (a -> a) (b -> b) (Endo a) (Endo b) | |
| Wrapped (b -> a) (b' -> a') (Op a b) (Op a' b') | |
| (ArrowApply m, ArrowApply n) => Wrapped (m () a) (n () b) (ArrowMonad m a) (ArrowMonad n b) | |
| Wrapped ((a -> m r) -> m r) ((a' -> m' r') -> m' r') (ContT r m a) (ContT r' m' a') | |
| Wrapped (s -> m (a, s)) (s' -> m' (a', s')) (StateT s m a) (StateT s' m' a') | |
| Wrapped (s -> m (a, s)) (s' -> m' (a', s')) (StateT s m a) (StateT s' m' a') | |
| Wrapped (r -> m a) (r' -> m' a') (ReaderT r m a) (ReaderT r' m' a') | |
| Wrapped (a -> m b) (u -> n v) (Kleisli m a b) (Kleisli n u v) | |
| Wrapped (Either (f a) (g a)) (Either (f' a') (g' a')) (Coproduct f g a) (Coproduct f' g' a') | |
| Wrapped (a b c) (u v w) (WrappedArrow a b c) (WrappedArrow u v w) | |
| Wrapped (r -> s -> m (a, s, w)) (r' -> s' -> m' (a', s', w')) (RWST r w s m a) (RWST r' w' s' m' a') | |
| Wrapped (r -> s -> m (a, s, w)) (r' -> s' -> m' (a', s', w')) (RWST r w s m a) (RWST r' w' s' m' a') | 
wrapped' :: Wrapped s s a a => Iso' s aSource
A convenient type-restricted version of wrapped for aiding type inference.
unwrapped' :: Wrapped s s a a => Iso' a sSource
A convenient type-restricted version of unwrapped for aiding type inference.
wrapping :: Wrapped s s a a => (s -> a) -> Iso s s a aSource
This is a convenient version of wrapped with an argument that's ignored.
The argument is used to specify which newtype the user intends to wrap by using the constructor for that newtype.
The user supplied function is ignored, merely its type is used.
unwrapping :: Wrapped s s a a => (s -> a) -> Iso a a s sSource
This is a convenient version of unwrapped with an argument that's ignored.
The argument is used to specify which newtype the user intends to remove by using the constructor for that newtype.
The user supplied function is ignored, merely its type is used.
wrappings :: Wrapped s t a b => (s -> a) -> (t -> b) -> Iso s t a bSource
This is a convenient version of wrapped with two arguments that are ignored.
These arguments are used to which newtype the user intends to wrap and should both be the same constructor. This redundancy is necessary in order to find the full polymorphic isomorphism family.
The user supplied functions are ignored, merely their types are used.
unwrappings :: Wrapped t s b a => (s -> a) -> (t -> b) -> Iso a b s tSource
This is a convenient version of unwrapped with two arguments that are ignored.
These arguments are used to which newtype the user intends to remove and should both be the same constructor. This redundancy is necessary in order to find the full polymorphic isomorphism family.
The user supplied functions are ignored, merely their types are used.
ala :: Wrapped s s a a => (s -> a) -> ((s -> a) -> e -> a) -> e -> sSource
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