Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type Iso s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type Iso' s a = Iso s s a a
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- from :: AnIso s t a b -> Iso b a t s
- under :: AnIso s t a b -> (t -> s) -> b -> a
- enum :: Enum a => Iso' Int a
- curried :: (Profunctor p, Functor f) => p (a -> b -> c) (f (d -> e -> f)) -> p ((a, b) -> c) (f ((d, e) -> f))
- uncurried :: (Profunctor p, Functor f) => p ((a, b) -> c) (f ((d, e) -> f)) -> p (a -> b -> c) (f (d -> e -> f))
- flipped :: (Profunctor p, Functor f) => p (b -> a -> c) (f (b' -> a' -> c')) -> p (a -> b -> c) (f (a' -> b' -> c'))
Iso
type Iso s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Profunctor p, Functor f) => p a (f b) -> p s (f t) #
enum :: Enum a => Iso' Int a #
This isomorphism can be used to convert to or from an instance of Enum
.
>>>
LT^.from enum
0
>>>
97^.enum :: Char
'a'
Note: this is only an isomorphism from the numeric range actually used
and it is a bit of a pleasant fiction, since there are questionable
Enum
instances for Double
, and Float
that exist solely for
[1.0 .. 4.0]
sugar and the instances for those and Integer
don't
cover all values in their range.
curried :: (Profunctor p, Functor f) => p (a -> b -> c) (f (d -> e -> f)) -> p ((a, b) -> c) (f ((d, e) -> f)) #
uncurried :: (Profunctor p, Functor f) => p ((a, b) -> c) (f ((d, e) -> f)) -> p (a -> b -> c) (f (d -> e -> f)) #
flipped :: (Profunctor p, Functor f) => p (b -> a -> c) (f (b' -> a' -> c')) -> p (a -> b -> c) (f (a' -> b' -> c')) #
The isomorphism for flipping a function.
>>>
((,)^.flipped) 1 2
(2,1)