Portability | non-portable |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- type Prism s t a b = forall k f. (Prismatic k, Applicative f) => k (a -> f b) (s -> f t)
- type APrism s t a b = Overloaded Prismoid Mutator s t a b
- class Isomorphic k => Prismatic k where
- prism :: Applicative f => (b -> t) -> (s -> Either t a) -> k (a -> f b) (s -> f t)
- data Prismoid ab st where
- clonePrism :: APrism s t a b -> Prism s t a b
- remit :: APrism s t a b -> Getter b t
- review :: MonadReader b m => APrism s t a b -> m t
- reviews :: MonadReader b m => APrism s t a b -> (t -> r) -> m r
- reuse :: MonadState b m => APrism s t a b -> m t
- reuses :: MonadState b m => APrism s t a b -> (t -> r) -> m r
- outside :: APrism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r)
- aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)
- without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)
- _left :: Prism (Either a c) (Either b c) a b
- _right :: Prism (Either c a) (Either c b) a b
- _just :: Prism (Maybe a) (Maybe b) a b
- type SimplePrism s a = Prism s s a a
Prisms
type Prism s t a b = forall k f. (Prismatic k, Applicative f) => k (a -> f b) (s -> f t)Source
A Prism
l
is a 0-or-1 target Traversal
that can also be turned around with remit
to
obtain a Getter
in the opposite direction.
There are two laws that a Prism
should satisfy:
First, if I remit
or review
a value with a Prism
and then preview
or use (^?
), I will get it back:
Second, if you can extract a value a
using a Prism l
from a value s
, then the value s
is completely described my l
and a
:
These two laws imply that the Traversal
laws hold for every Prism
and that we traverse
at most 1 element:
lengthOf
l x<=
1
It may help to think of this as a Iso
that can be partial in one direction.
Every Prism
is a valid Traversal
.
For example, you might have a
allows you to always
go from a Simple
Prism
Integer
NaturalNatural
to an Integer
, and provide you with tools to check if an Integer
is
a Natural
and/or to edit one if it is.
nat
::Simple
Prism
Integer
Natural
nat
=prism
toInteger
$
\ i -> if i<
0 thenLeft
i elseRight
(fromInteger
i)
Now we can ask if an Integer
is a Natural
.
>>>
5^?nat
Just 5
>>>
(-5)^?nat
Nothing
We can update the ones that are:
>>>
(-3,4) & both.nat *~ 2
(-3,8)
And we can then convert from a Natural
to an Integer
.
>>>
5 ^. remit nat -- :: Natural
5
Similarly we can use a Prism
to traverse
the left half of an Either
:
>>>
Left "hello" & _left %~ length
Left 5
or to construct an Either
:
>>>
5^.remit _left
Left 5
such that if you query it with the Prism
, you will get your original input back.
>>>
5^.remit _left ^? _left
Just 5
Another interesting way to think of a Prism
is as the categorical dual of a Lens
-- a co-Lens
, so to speak. This is what permits the construction of outside
.
type APrism s t a b = Overloaded Prismoid Mutator s t a bSource
If you see this in a signature for a function, the function is expecting a Prism
,
not some kind of alien invader.
Constructing Prisms
class Isomorphic k => Prismatic k whereSource
Used to provide overloading of prisms.
An instance of Prismatic
is a Category
with a canonical mapping to it from the category
of embedding-projection pairs over Haskell types.
prism :: Applicative f => (b -> t) -> (s -> Either t a) -> k (a -> f b) (s -> f t)Source
data Prismoid ab st whereSource
This data type is used to capture all of the information provided by the
Prismatic
class, so you can turn a Prism
around into a Getter
or
otherwise muck around with its internals.
If you see a function that expects a Prismoid
or APrism
, it is probably
just expecting a Prism
.
Consuming Prisms
clonePrism :: APrism s t a b -> Prism s t a bSource
review :: MonadReader b m => APrism s t a b -> m tSource
This can be used to turn an Iso
or Prism
around and view
a value (or the current environment) through it the other way.
review
≡view
.
remit
>>>
review _left "mustard"
Left "mustard"
Usually review
is used in the (->)
monad with a Simple
Prism
or Iso
, in which case it may be useful to think of
it as having one of these more restricted type signatures:
review
::Simple
Iso
s a -> a -> sreview
::Simple
Prism
s a -> a -> s
However, when working with a monad transformer stack, it is sometimes useful to be able to review
the current environment, in which case one of
these more slightly more liberal type signatures may be beneficial to think of it as having:
review
::MonadReader
a m =>Simple
Iso
s a -> m sreview
::MonadReader
a m =>Simple
Prism
s a -> m s
reviews :: MonadReader b m => APrism s t a b -> (t -> r) -> m rSource
This can be used to turn an Iso
or Prism
around and view
a value (or the current environment) through it the other way,
applying a function.
reviews
≡views
.
remit
>>>
reviews _left isRight "mustard"
False
Usually this function is used in the (->)
monad with a Simple
Prism
or Iso
, in which case it may be useful to think of
it as having one of these more restricted type signatures:
reviews
::Simple
Iso
s a -> (s -> r) -> a -> rreviews
::Simple
Prism
s a -> (s -> r) -> a -> r
However, when working with a monad transformer stack, it is sometimes useful to be able to review
the current environment, in which case one of
these more slightly more liberal type signatures may be beneficial to think of it as having:
reviews
::MonadReader
a m =>Simple
Iso
s a -> (s -> r) -> m rreviews
::MonadReader
a m =>Simple
Prism
s a -> (s -> r) -> m r
reuse :: MonadState b m => APrism s t a b -> m tSource
reuses :: MonadState b m => APrism s t a b -> (t -> r) -> m rSource
This can be used to turn an Iso
or Prism
around and use
the current state through it the other way,
applying a function.
reuses
≡uses
.
remit
>>>
evalState (reuses _left isLeft) (5 :: Int)
True
reuses
::MonadState
a m =>Simple
Prism
s a -> (s -> r) -> m rreuses
::MonadState
a m =>Simple
Iso
s a -> (s -> r) -> m r
aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)Source
Use a Prism
to work over part of a structure.
without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)Source
Common Prisms
_left :: Prism (Either a c) (Either b c) a bSource
This prism provides a traversal for tweaking the left-hand value of an Either
:
>>>
over _left (+1) (Left 2)
Left 3
>>>
over _left (+1) (Right 2)
Right 2
>>>
Right 42 ^._left :: String
""
>>>
Left "hello" ^._left
"hello"
It also can be turned around to obtain the embedding into the Left
half of an Either
:
>>>
5^.remit _left
Left 5
_right :: Prism (Either c a) (Either c b) a bSource
This prism provides a traversal for tweaking the right-hand value of an Either
:
>>>
over _right (+1) (Left 2)
Left 2
>>>
over _right (+1) (Right 2)
Right 3
>>>
Right "hello" ^._right
"hello"
>>>
Left "hello" ^._right :: [Double]
[]
It also can be turned around to obtain the embedding into the Right
half of an Either
:
>>>
5^.remit _right
Right 5
(Unfortunately the instance for
is still missing from base,
so this can't just be Traversable
(Either
c)traverse
.)
Simple
type SimplePrism s a = Prism s s a aSource