lens-5.2.3: Lenses, Folds and Traversals
Copyright(C) 2012-16 Edward Kmett Michael Sloan
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
PortabilityRank2, MPTCs, fundeps
Safe HaskellTrustworthy
LanguageHaskell2010

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.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 :: Type Source #

type Unwrapped s = GUnwrapped (Rep s)

Methods

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

An isomorphism between s and a.

If your type has a Generic instance, _Wrapped' will default to _GWrapped', and you can choose to not override it with your own definition.

default _Wrapped' :: (Generic s, D1 d (C1 c (S1 s' (Rec0 a))) ~ Rep s, Unwrapped s ~ GUnwrapped (Rep s)) => Iso' s (Unwrapped s) Source #

Instances

Instances details
Wrapped NoMethodError Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped NoMethodError Source #

Wrapped PatternMatchFail Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped PatternMatchFail Source #

Wrapped RecConError Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecConError Source #

Wrapped RecSelError Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecSelError Source #

Wrapped RecUpdError Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecUpdError Source #

Wrapped TypeError Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped TypeError Source #

Wrapped All Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped All Source #

Wrapped Any Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Any Source #

Wrapped Errno Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Errno Source #

Wrapped CBool Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBool Source #

Wrapped CChar Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CChar Source #

Wrapped CClock Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CClock Source #

Wrapped CDouble Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CDouble Source #

Wrapped CFloat Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFloat Source #

Wrapped CInt Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CInt Source #

Wrapped CIntMax Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIntMax Source #

Wrapped CIntPtr Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIntPtr Source #

Wrapped CLLong Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLLong Source #

Wrapped CLong Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLong Source #

Wrapped CPtrdiff Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CPtrdiff Source #

Wrapped CSChar Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSChar Source #

Wrapped CSUSeconds Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSUSeconds Source #

Wrapped CShort Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CShort Source #

Wrapped CSigAtomic Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSigAtomic Source #

Wrapped CSize Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSize Source #

Wrapped CTime Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTime Source #

Wrapped CUChar Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUChar Source #

Wrapped CUInt Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUInt Source #

Wrapped CUIntMax Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUIntMax Source #

Wrapped CUIntPtr Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUIntPtr Source #

Wrapped CULLong Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULLong Source #

Wrapped CULong Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULong Source #

Wrapped CUSeconds Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUSeconds Source #

Wrapped CUShort Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUShort Source #

Wrapped CWchar Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CWchar Source #

Wrapped ErrorCall Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped ErrorCall Source #

Wrapped AssertionFailed Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped AssertionFailed Source #

Wrapped CompactionFailed Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CompactionFailed Source #

Wrapped CBlkCnt Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBlkCnt Source #

Wrapped CBlkSize Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBlkSize Source #

Wrapped CCc Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CCc Source #

Wrapped CClockId Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CClockId Source #

Wrapped CDev Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CDev Source #

Wrapped CFsBlkCnt Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFsBlkCnt Source #

Wrapped CFsFilCnt Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFsFilCnt Source #

Wrapped CGid Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CGid Source #

Wrapped CId Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CId Source #

Wrapped CIno Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIno Source #

Wrapped CKey Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CKey Source #

Wrapped CMode Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CMode Source #

Wrapped CNlink Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CNlink Source #

Wrapped COff Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped COff Source #

Wrapped CPid Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CPid Source #

Wrapped CRLim Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CRLim Source #

Wrapped CSpeed Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSpeed Source #

Wrapped CSsize Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSsize Source #

Wrapped CTcflag Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTcflag Source #

Wrapped CTimer Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTimer Source #

Wrapped CUid Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUid Source #

Wrapped Fd Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Fd Source #

Wrapped IntSet Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped IntSet Source #

Wrapped (ZipList a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ZipList a) Source #

Wrapped (Comparison a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Comparison a) Source #

Wrapped (Equivalence a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Equivalence a) Source #

Wrapped (Predicate a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Predicate a) Source #

Wrapped (Identity a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Identity a) Source #

Wrapped (First a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (First a) Source #

Methods

_Wrapped' :: Iso' (First a) (Unwrapped (First a)) Source #

Wrapped (Last a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Last a) Source #

Methods

_Wrapped' :: Iso' (Last a) (Unwrapped (Last a)) Source #

Wrapped (Down a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Down a) Source #

Methods

_Wrapped' :: Iso' (Down a) (Unwrapped (Down a)) Source #

Wrapped (First a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (First a) Source #

Methods

_Wrapped' :: Iso' (First a) (Unwrapped (First a)) Source #

Wrapped (Last a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Last a) Source #

Methods

_Wrapped' :: Iso' (Last a) (Unwrapped (Last a)) Source #

Wrapped (Max a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Max a) Source #

Methods

_Wrapped' :: Iso' (Max a) (Unwrapped (Max a)) Source #

Wrapped (Min a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Min a) Source #

Methods

_Wrapped' :: Iso' (Min a) (Unwrapped (Min a)) Source #

Wrapped (WrappedMonoid a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedMonoid a) Source #

Wrapped (Dual a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Dual a) Source #

Methods

_Wrapped' :: Iso' (Dual a) (Unwrapped (Dual a)) Source #

Wrapped (Endo a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Endo a) Source #

Methods

_Wrapped' :: Iso' (Endo a) (Unwrapped (Endo a)) Source #

Wrapped (Product a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Product a) Source #

Wrapped (Sum a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Sum a) Source #

Methods

_Wrapped' :: Iso' (Sum a) (Unwrapped (Sum a)) Source #

Wrapped (Par1 p) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Par1 p) Source #

Methods

_Wrapped' :: Iso' (Par1 p) (Unwrapped (Par1 p)) Source #

Wrapped (IntMap a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IntMap a) Source #

Wrapped (Seq a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Seq a) Source #

Methods

_Wrapped' :: Iso' (Seq a) (Unwrapped (Seq a)) Source #

Ord a => Wrapped (Set a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Set a) Source #

Methods

_Wrapped' :: Iso' (Set a) (Unwrapped (Set a)) Source #

(Hashable a, Eq a) => Wrapped (HashSet a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (HashSet a) Source #

Wrapped (Vector a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) Source #

Prim a => Wrapped (Vector a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) Source #

Storable a => Wrapped (Vector a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) Source #

Unbox a => Wrapped (Vector a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) Source #

Wrapped (NonEmpty a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (NonEmpty a) Source #

Wrapped (WrappedMonad m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedMonad m a) Source #

Wrapped (ArrowMonad m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ArrowMonad m a) Source #

Wrapped (Op a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Op a b) Source #

Methods

_Wrapped' :: Iso' (Op a b) (Unwrapped (Op a b)) Source #

Ord k => Wrapped (Map k a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Map k a) Source #

Methods

_Wrapped' :: Iso' (Map k a) (Unwrapped (Map k a)) Source #

Wrapped (CatchT m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CatchT m a) Source #

Methods

_Wrapped' :: Iso' (CatchT m a) (Unwrapped (CatchT m a)) Source #

Wrapped (Alt f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Alt f a) Source #

Methods

_Wrapped' :: Iso' (Alt f a) (Unwrapped (Alt f a)) Source #

Wrapped (CoiterT w a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CoiterT w a) Source #

Methods

_Wrapped' :: Iso' (CoiterT w a) (Unwrapped (CoiterT w a)) Source #

Wrapped (IterT m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IterT m a) Source #

Methods

_Wrapped' :: Iso' (IterT m a) (Unwrapped (IterT m a)) Source #

Wrapped (MaybeApply f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (MaybeApply f a) Source #

Wrapped (WrappedApplicative f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedApplicative f a) Source #

Wrapped (ListT m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ListT m a) Source #

Methods

_Wrapped' :: Iso' (ListT m a) (Unwrapped (ListT m a)) Source #

Wrapped (MaybeT m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (MaybeT m a) Source #

Methods

_Wrapped' :: Iso' (MaybeT m a) (Unwrapped (MaybeT m a)) Source #

(Hashable k, Eq k) => Wrapped (HashMap k a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (HashMap k a) Source #

Methods

_Wrapped' :: Iso' (HashMap k a) (Unwrapped (HashMap k a)) Source #

Wrapped (WrappedArrow a b c) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedArrow a b c) Source #

Wrapped (Kleisli m a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Kleisli m a b) Source #

Methods

_Wrapped' :: Iso' (Kleisli m a b) (Unwrapped (Kleisli m a b)) Source #

Wrapped (Const a x) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Const a x) Source #

Methods

_Wrapped' :: Iso' (Const a x) (Unwrapped (Const a x)) Source #

Wrapped (Ap f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Ap f a) Source #

Methods

_Wrapped' :: Iso' (Ap f a) (Unwrapped (Ap f a)) Source #

Wrapped (Alt f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Alt f a) Source #

Methods

_Wrapped' :: Iso' (Alt f a) (Unwrapped (Alt f a)) Source #

Wrapped (Rec1 f p) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Rec1 f p) Source #

Methods

_Wrapped' :: Iso' (Rec1 f p) (Unwrapped (Rec1 f p)) Source #

Wrapped (Fix p a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Fix p a) Source #

Methods

_Wrapped' :: Iso' (Fix p a) (Unwrapped (Fix p a)) Source #

Wrapped (Join p a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Join p a) Source #

Methods

_Wrapped' :: Iso' (Join p a) (Unwrapped (Join p a)) Source #

Wrapped (TracedT m w a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (TracedT m w a) Source #

Methods

_Wrapped' :: Iso' (TracedT m w a) (Unwrapped (TracedT m w a)) Source #

Wrapped (Compose f g a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Compose f g a) Source #

Methods

_Wrapped' :: Iso' (Compose f g a) (Unwrapped (Compose f g a)) Source #

Wrapped (ComposeCF f g a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ComposeCF f g a) Source #

Methods

_Wrapped' :: Iso' (ComposeCF f g a) (Unwrapped (ComposeCF f g a)) Source #

Wrapped (ComposeFC f g a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ComposeFC f g a) Source #

Methods

_Wrapped' :: Iso' (ComposeFC f g a) (Unwrapped (ComposeFC f g a)) Source #

Wrapped (ApT f g a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ApT f g a) Source #

Methods

_Wrapped' :: Iso' (ApT f g a) (Unwrapped (ApT f g a)) Source #

Wrapped (CofreeT f w a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CofreeT f w a) Source #

Methods

_Wrapped' :: Iso' (CofreeT f w a) (Unwrapped (CofreeT f w a)) Source #

Wrapped (FreeT f m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (FreeT f m a) Source #

Methods

_Wrapped' :: Iso' (FreeT f m a) (Unwrapped (FreeT f m a)) Source #

Wrapped (Static f a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Static f a b) Source #

Methods

_Wrapped' :: Iso' (Static f a b) (Unwrapped (Static f a b)) Source #

Wrapped (Tagged s a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Tagged s a) Source #

Methods

_Wrapped' :: Iso' (Tagged s a) (Unwrapped (Tagged s a)) Source #

Wrapped (Backwards f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Backwards f a) Source #

Wrapped (ErrorT e m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ErrorT e m a) Source #

Methods

_Wrapped' :: Iso' (ErrorT e m a) (Unwrapped (ErrorT e m a)) Source #

Wrapped (ExceptT e m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ExceptT e m a) Source #

Methods

_Wrapped' :: Iso' (ExceptT e m a) (Unwrapped (ExceptT e m a)) Source #

Wrapped (IdentityT m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IdentityT m a) Source #

Wrapped (ReaderT r m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ReaderT r m a) Source #

Methods

_Wrapped' :: Iso' (ReaderT r m a) (Unwrapped (ReaderT r m a)) Source #

Wrapped (StateT s m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (StateT s m a) Source #

Methods

_Wrapped' :: Iso' (StateT s m a) (Unwrapped (StateT s m a)) Source #

Wrapped (StateT s m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (StateT s m a) Source #

Methods

_Wrapped' :: Iso' (StateT s m a) (Unwrapped (StateT s m a)) Source #

Wrapped (WriterT w m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WriterT w m a) Source #

Methods

_Wrapped' :: Iso' (WriterT w m a) (Unwrapped (WriterT w m a)) Source #

Wrapped (WriterT w m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WriterT w m a) Source #

Methods

_Wrapped' :: Iso' (WriterT w m a) (Unwrapped (WriterT w m a)) Source #

Wrapped (Constant a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Constant a b) Source #

Methods

_Wrapped' :: Iso' (Constant a b) (Unwrapped (Constant a b)) Source #

Wrapped (Reverse f a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Reverse f a) Source #

Methods

_Wrapped' :: Iso' (Reverse f a) (Unwrapped (Reverse f a)) Source #

Wrapped (K1 i c p) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (K1 i c p) Source #

Methods

_Wrapped' :: Iso' (K1 i c p) (Unwrapped (K1 i c p)) Source #

Wrapped (Costar f d c) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Costar f d c) Source #

Methods

_Wrapped' :: Iso' (Costar f d c) (Unwrapped (Costar f d c)) Source #

Wrapped (Forget r a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Forget r a b) Source #

Methods

_Wrapped' :: Iso' (Forget r a b) (Unwrapped (Forget r a b)) Source #

Wrapped (Star f d c) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Star f d c) Source #

Methods

_Wrapped' :: Iso' (Star f d c) (Unwrapped (Star f d c)) Source #

Wrapped (ContT r m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ContT r m a) Source #

Methods

_Wrapped' :: Iso' (ContT r m a) (Unwrapped (ContT r m a)) Source #

Wrapped (Compose f g a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Compose f g a) Source #

Methods

_Wrapped' :: Iso' (Compose f g a) (Unwrapped (Compose f g a)) Source #

Wrapped ((f :.: g) p) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped ((f :.: g) p) Source #

Methods

_Wrapped' :: Iso' ((f :.: g) p) (Unwrapped ((f :.: g) p)) Source #

Wrapped (M1 i c f p) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (M1 i c f p) Source #

Methods

_Wrapped' :: Iso' (M1 i c f p) (Unwrapped (M1 i c f p)) Source #

Wrapped (Clown f a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Clown f a b) Source #

Methods

_Wrapped' :: Iso' (Clown f a b) (Unwrapped (Clown f a b)) Source #

Wrapped (Flip p a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Flip p a b) Source #

Methods

_Wrapped' :: Iso' (Flip p a b) (Unwrapped (Flip p a b)) Source #

Wrapped (Joker g a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Joker g a b) Source #

Methods

_Wrapped' :: Iso' (Joker g a b) (Unwrapped (Joker g a b)) Source #

Wrapped (WrappedBifunctor p a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedBifunctor p a b) Source #

Wrapped (WrappedArrow p a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedArrow p a b) Source #

Wrapped (Semi m a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Semi m a b) Source #

Methods

_Wrapped' :: Iso' (Semi m a b) (Unwrapped (Semi m a b)) Source #

Wrapped (WrappedCategory k3 a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedCategory k3 a b) Source #

Wrapped (Dual k3 a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Dual k3 a b) Source #

Methods

_Wrapped' :: Iso' (Dual k3 a b) (Unwrapped (Dual k3 a b)) Source #

Wrapped (RWST r w s m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (RWST r w s m a) Source #

Methods

_Wrapped' :: Iso' (RWST r w s m a) (Unwrapped (RWST r w s m a)) Source #

Wrapped (RWST r w s m a) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (RWST r w s m a) Source #

Methods

_Wrapped' :: Iso' (RWST r w s m a) (Unwrapped (RWST r w s m a)) Source #

Wrapped (Tannen f p a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Tannen f p a b) Source #

Methods

_Wrapped' :: Iso' (Tannen f p a b) (Unwrapped (Tannen f p a b)) Source #

Wrapped (Cayley f p a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Cayley f p a b) Source #

Methods

_Wrapped' :: Iso' (Cayley f p a b) (Unwrapped (Cayley f p a b)) Source #

Wrapped (Biff p f g a b) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Biff p f g a b) Source #

Methods

_Wrapped' :: Iso' (Biff p f g a b) (Unwrapped (Biff p f g a b)) 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 :: Type) (t :: Type) Source #

Instances

Instances details
t ~ NoMethodError => Rewrapped NoMethodError t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ PatternMatchFail => Rewrapped PatternMatchFail t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ RecConError => Rewrapped RecConError t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ RecSelError => Rewrapped RecSelError t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ RecUpdError => Rewrapped RecUpdError t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ TypeError => Rewrapped TypeError t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ All => Rewrapped All t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Any => Rewrapped Any t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped Errno t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CBool t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CChar t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CClock t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CDouble t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CFloat t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CInt t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CIntMax t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CIntPtr t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CLLong t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CLong t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CPtrdiff t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSChar t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSUSeconds t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CShort t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSigAtomic t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSize t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CTime t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUChar t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUInt t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUIntMax t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUIntPtr t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CULLong t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CULong t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUSeconds t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUShort t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CWchar t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ErrorCall => Rewrapped ErrorCall t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ AssertionFailed => Rewrapped AssertionFailed t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ CompactionFailed => Rewrapped CompactionFailed t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CBlkCnt t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CBlkSize t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CCc t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CClockId t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CDev t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CFsBlkCnt t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CFsFilCnt t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CGid t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CId t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CIno t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CKey t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CMode t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CNlink t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped COff t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CPid t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CRLim t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSpeed t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CSsize t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CTcflag t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CTimer t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped CUid t Source # 
Instance details

Defined in Control.Lens.Wrapped

Rewrapped Fd t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ IntSet => Rewrapped IntSet t Source #

Use _Wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

t ~ ZipList b => Rewrapped (ZipList a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Comparison b => Rewrapped (Comparison a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Equivalence b => Rewrapped (Equivalence a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Predicate b => Rewrapped (Predicate a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Identity b => Rewrapped (Identity a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ First b => Rewrapped (First a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Last b => Rewrapped (Last a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Down b => Rewrapped (Down a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ First b => Rewrapped (First a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Last b => Rewrapped (Last a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Max b => Rewrapped (Max a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Min b => Rewrapped (Min a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedMonoid b => Rewrapped (WrappedMonoid a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Dual b => Rewrapped (Dual a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Endo b => Rewrapped (Endo a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Product b => Rewrapped (Product a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Sum b => Rewrapped (Sum a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Par1 p' => Rewrapped (Par1 p) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ IntMap a' => Rewrapped (IntMap a) t Source #

Use _Wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

t ~ Seq a' => Rewrapped (Seq a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

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

Use _Wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

(t ~ HashSet a', Hashable a, Eq a) => Rewrapped (HashSet a) t Source #

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

Instance details

Defined in Control.Lens.Wrapped

t ~ Vector a' => Rewrapped (Vector a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

(Prim a, t ~ Vector a') => Rewrapped (Vector a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

(Storable a, t ~ Vector a') => Rewrapped (Vector a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ NonEmpty b => Rewrapped (NonEmpty a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedMonad m' a' => Rewrapped (WrappedMonad m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ArrowMonad m' a' => Rewrapped (ArrowMonad m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Op a' b' => Rewrapped (Op a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t Source #

Use _Wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

t ~ CatchT m' a' => Rewrapped (CatchT m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Alt f' a' => Rewrapped (Alt f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ CoiterT w' a' => Rewrapped (CoiterT w a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ IterT m' a' => Rewrapped (IterT m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ MaybeApply f' a' => Rewrapped (MaybeApply f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedApplicative f' a' => Rewrapped (WrappedApplicative f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ListT n b => Rewrapped (ListT m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ MaybeT n b => Rewrapped (MaybeT m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

(t ~ HashMap k' a', Hashable k, Eq k) => Rewrapped (HashMap k a) t Source #

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

Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedArrow a' b' c' => Rewrapped (WrappedArrow a b c) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Kleisli m' a' b' => Rewrapped (Kleisli m a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Const a' x' => Rewrapped (Const a x) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Ap g b => Rewrapped (Ap f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Alt g b => Rewrapped (Alt f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Rec1 f' p' => Rewrapped (Rec1 f p) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Fix p' a' => Rewrapped (Fix p a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Join p' a' => Rewrapped (Join p a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ TracedT m' w' a' => Rewrapped (TracedT m w a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Compose f' g' a' => Rewrapped (Compose f g a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ComposeCF f' g' a' => Rewrapped (ComposeCF f g a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ComposeFC f' g' a' => Rewrapped (ComposeFC f g a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ApT f' g' a' => Rewrapped (ApT f g a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ CofreeT f' w' a' => Rewrapped (CofreeT f w a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ FreeT f' m' a' => Rewrapped (FreeT f m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Static f' a' b' => Rewrapped (Static f a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Tagged s' a' => Rewrapped (Tagged s a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Backwards g b => Rewrapped (Backwards f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ErrorT e' m' a' => Rewrapped (ErrorT e m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ExceptT e' m' a' => Rewrapped (ExceptT e m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ IdentityT n b => Rewrapped (IdentityT m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ReaderT s n b => Rewrapped (ReaderT r m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ StateT s' m' a' => Rewrapped (StateT s m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ StateT s' m' a' => Rewrapped (StateT s m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WriterT w' m' a' => Rewrapped (WriterT w m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WriterT w' m' a' => Rewrapped (WriterT w m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Constant a' b' => Rewrapped (Constant a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Reverse g b => Rewrapped (Reverse f a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ K1 i' c' p' => Rewrapped (K1 i c p) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Costar f' d' c' => Rewrapped (Costar f d c) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Forget r' a' b' => Rewrapped (Forget r a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Star f' d' c' => Rewrapped (Star f d c) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ ContT r' m' a' => Rewrapped (ContT r m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Compose f' g' a' => Rewrapped (Compose f g a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ (f' :.: g') p' => Rewrapped ((f :.: g) p) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ M1 i' c' f' p' => Rewrapped (M1 i c f p) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Clown f' a' b' => Rewrapped (Clown f a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Flip p' a' b' => Rewrapped (Flip p a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Joker g' a' b' => Rewrapped (Joker g a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedBifunctor p' a' b' => Rewrapped (WrappedBifunctor p a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedArrow p' a' b' => Rewrapped (WrappedArrow p a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Semi m' a' b' => Rewrapped (Semi m a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ WrappedCategory k' a' b' => Rewrapped (WrappedCategory k6 a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Dual k' a' b' => Rewrapped (Dual k6 a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ RWST r' w' s' m' a' => Rewrapped (RWST r w s m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ RWST r' w' s' m' a' => Rewrapped (RWST r w s m a) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Tannen f' p' a' b' => Rewrapped (Tannen f p a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Cayley f' p' a' b' => Rewrapped (Cayley f p a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

t ~ Biff p' f' g' a' b' => Rewrapped (Biff p f g a b) t Source # 
Instance details

Defined in Control.Lens.Wrapped

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

Instances

Instances details
(Rewrapped s t, Rewrapped t s) => Rewrapping s t Source # 
Instance details

Defined in Control.Lens.Wrapped

_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 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 :: Rewrapped t t => t -> Unwrapped t Source #

Generics

_GWrapped' :: (Generic s, D1 d (C1 c (S1 s' (Rec0 a))) ~ Rep s, Unwrapped s ~ GUnwrapped (Rep s)) => Iso' s (Unwrapped s) Source #

Implement the _Wrapped operation for a type using its Generic instance.