Portability | Rank2, MPTCs, fundeps |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
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.overSum
f ≡_Unwrapping
Sum
%~
f Control.Newtype.underSum
f ≡_Wrapping
Sum
%~
f Control.Newtype.overFSum
f ≡mapping
(_Unwrapping
Sum
)%~
f Control.Newtype.underFSum
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.
- class Wrapped s where
- _Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s
- _Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s)
- _Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s
- class Wrapped s => Rewrapped s t
- class (Rewrapped s t, Rewrapped t s) => Rewrapping s t
- _Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t s
- _Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s
- op :: Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s
- ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped s
- alaf :: (Profunctor p, Rewrapping s t) => (Unwrapped s -> s) -> (p r t -> e -> s) -> p r (Unwrapped t) -> e -> Unwrapped s
Wrapping and Unwrapping monomorphically
Wrapped
provides isomorphisms to wrap and unwrap newtypes or
data types with one constructor.
_Unwrapped' :: Wrapped s => Iso' (Unwrapped s) sSource
_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) sSource
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
~ * t PatternMatchFail => Rewrapped PatternMatchFail t | |
~ * t RecSelError => Rewrapped RecSelError t | |
~ * t RecConError => Rewrapped RecConError t | |
~ * t RecUpdError => Rewrapped RecUpdError t | |
~ * t NoMethodError => Rewrapped NoMethodError t | |
~ * t AssertionFailed => Rewrapped AssertionFailed t | |
~ * t All => Rewrapped All t | |
~ * t Any => Rewrapped Any t | |
~ * t ErrorCall => Rewrapped ErrorCall t | |
~ * t IntSet => Rewrapped IntSet t | Use |
~ * t (ZipList b) => Rewrapped (ZipList a) t | |
~ * t (Dual b) => Rewrapped (Dual a) t | |
~ * t (Endo b) => Rewrapped (Endo b) t | |
~ * t (Sum b) => Rewrapped (Sum a) t | |
~ * t (Product b) => Rewrapped (Product a) t | |
~ * t (First b) => Rewrapped (First a) t | |
~ * t (Last b) => Rewrapped (Last b) t | |
~ * t (Identity b) => Rewrapped (Identity a) t | |
~ * t (Seq a') => Rewrapped (Seq a) t | |
~ * t (IntMap a') => Rewrapped (IntMap a) t | Use |
(~ * t (Set a'), Ord a) => Rewrapped (Set a) t | Use |
~ * t (Predicate b) => Rewrapped (Predicate a) t | |
~ * t (Comparison b) => Rewrapped (Comparison a) t | |
~ * t (Equivalence b) => Rewrapped (Equivalence a) t | |
~ * t (Min b) => Rewrapped (Min a) t | |
~ * t (Max b) => Rewrapped (Max a) t | |
~ * t (First b) => Rewrapped (First a) t | |
~ * t (Last b) => Rewrapped (Last a) t | |
~ * t (WrappedMonoid b) => Rewrapped (WrappedMonoid a) t | |
~ * t (Option b) => Rewrapped (Option a) t | |
(~ * t (HashSet a'), Hashable a, Eq a) => Rewrapped (HashSet a) t | Use |
(~ * t (HashMap k' a'), Hashable k, Eq k) => Rewrapped (HashMap k a) t | Use |
(~ * t (Map k' a'), Ord k) => Rewrapped (Map k a) t | Use |
~ * t (Const a' x') => Rewrapped (Const a x) t | |
~ * t (WrappedMonad m' a') => Rewrapped (WrappedMonad m a) t | |
(~ * t (ArrowMonad m' a'), ArrowApply m, ArrowApply m') => Rewrapped (ArrowMonad m a) t | |
~ * t (IdentityT n b) => Rewrapped (IdentityT m a) t | |
~ * t (Op a' b') => Rewrapped (Op a b) t | |
~ * t (ListT n b) => Rewrapped (ListT m a) t | |
~ * t (Reverse g b) => Rewrapped (Reverse f a) t | |
~ * t (Backwards g b) => Rewrapped (Backwards f a) t | |
~ * t (Constant a' b') => Rewrapped (Constant a b) t | |
~ * t (MaybeT n b) => Rewrapped (MaybeT m a) t | |
~ * t (WrappedArrow a' b' c') => Rewrapped (WrappedArrow a b c) t | |
~ * t (Kleisli m' a' b') => Rewrapped (Kleisli m a b) t | |
~ * t (Coproduct f' g' a') => Rewrapped (Coproduct f g a) t | |
~ * t (TracedT m' w' a') => Rewrapped (TracedT m w a) t | |
~ * t (Compose f' g' a') => Rewrapped (Compose f g a) t | |
~ * t (ComposeFC f' g' a') => Rewrapped (ComposeFC f g a) t | |
~ * t (ComposeCF f' g' a') => Rewrapped (ComposeCF f g a) t | |
~ * t (ContT r' m' a') => Rewrapped (ContT r m a) t | |
~ * t (ErrorT e' m' a') => Rewrapped (ErrorT e m a) t | |
~ * t (ReaderT r n b) => Rewrapped (ReaderT r m a) t | |
~ * t (StateT s' m' a') => Rewrapped (StateT s m a) t | |
~ * t (StateT s' m' a') => Rewrapped (StateT s m a) t | |
~ * t (WriterT w' m' a') => Rewrapped (WriterT w m a) t | |
~ * t (WriterT w' m' a') => Rewrapped (WriterT w m a) t | |
~ * t (Compose f' g' a') => Rewrapped (Compose f g a) t | |
~ * t (Tagged k s' a') => Rewrapped (Tagged k1 s a) t | |
~ * t (RWST r' w' s' m' a') => Rewrapped (RWST r w s m a) t | |
~ * t (RWST r' w' s' m' a') => Rewrapped (RWST r w s m a) t |
class (Rewrapped s t, Rewrapped t s) => Rewrapping s t Source
(Rewrapped s t, Rewrapped t s) => Rewrapping s t |
_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)Source
Work under a newtype wrapper.
>>>
Const "hello" & _Wrapped %~ length & getConst
5
_Wrapped
≡from
_Unwrapped
_Unwrapped
≡from
_Wrapped
_Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t sSource
_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 sSource
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
ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped 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
alaf :: (Profunctor p, Rewrapping s t) => (Unwrapped s -> s) -> (p r t -> e -> s) -> p r (Unwrapped t) -> e -> Unwrapped 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.
>>>
alaf Sum foldMap length ["hello","world"]
10