Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Prism s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type Prism' s a = Prism s s a a
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
- is :: APrism s t a b -> s -> Bool
- only :: Eq a => a -> Prism' a ()
- class AsAny (sel :: k) a s | s sel k -> a where
- class AsSubtype sub sup where
- class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
- (<|) :: Cons s s a a => a -> s -> s
- cons :: Cons s s a a => a -> s -> s
- uncons :: Cons s s a a => s -> Maybe (a, s)
- _head :: Cons s s a a => Traversal' s a
- _tail :: Cons s s a a => Traversal' s s
- pattern (:<) :: forall b a. Cons b b a a => a -> b -> b
- class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
- (|>) :: Snoc s s a a => s -> a -> s
- snoc :: Snoc s s a a => s -> a -> s
- unsnoc :: Snoc s s a a => s -> Maybe (s, a)
- _init :: Snoc s s a a => Traversal' s s
- _last :: Snoc s s a a => Traversal' s a
- pattern (:>) :: forall a b. Snoc a a b b => a -> b -> a
- class AsEmpty a where
- pattern Empty :: forall s. AsEmpty s => s
Prism
type Prism s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p s (f t) #
A Prism
l
is a Traversal
that can also be turned
around with re
to obtain a Getter
in the
opposite direction.
There are two laws that a Prism
should satisfy:
First, if I re
or review
a value with a Prism
and then preview
or use (^?
), I will get it back:
preview
l (review
l b) ≡Just
b
Second, if you can extract a value a
using a Prism
l
from a value s
, then the value s
is completely described by l
and a
:
If
then preview
l s ≡ Just
areview
l a ≡ s
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 Prism'
Integer
Natural
Natural
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
::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 ^. re 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^.re _Left
Left 5
such that if you query it with the Prism
, you will get your original input back.
>>>
5^.re _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
.
Note: Composition with a Prism
is index-preserving.
AsAny
class AsAny (sel :: k) a s | s sel k -> a where #
Sums that have generic prisms.
A prism that projects a sum as identified by some selector. Currently
supported selectors are constructor names and unique types. Compatible
with the lens package's Prism
type.
>>>
dog ^? _As @"Dog"
Just (MkDog {name = "Shep", age = 3})
>>>
dog ^? _As @Dog
Just (MkDog {name = "Shep", age = 3})
>>>
dog ^? _As @"Cat"
Nothing
>>>
cat ^? _As @(Name, Age)
Just ("Mog",5)
>>>
cat ^? _As @"Cat"
Just ("Mog",5)
>>>
_As @"Cat" # ("Garfield", 6) :: Animal
Cat "Garfield" 6
>>>
duck ^? _As @Age
Just 2
Instances
AsConstructor ctor s s a a => AsAny (ctor :: Symbol) a s | |
Defined in Data.Generics.Sum.Any | |
AsType a s => AsAny (a :: *) a s | |
Defined in Data.Generics.Sum.Any |
AsSubtype
class AsSubtype sub sup where #
Structural subtyping between sums. A sum Sub
is a subtype of another sum
Sup
if a value of Sub
can be given (modulo naming of constructors)
whenever a value of Sup
is expected. In the running example for instance,
FourLeggedAnimal
is a subtype of Animal
since a value of the former can
be given as a value of the latter (renaming Dog4
to Dog
and Cat4
to
Cat
).
A prism that captures structural subtyping. Allows a substructure to be injected (upcast) into a superstructure or a superstructure to be downcast into a substructure (which may fail).
>>>
_Sub # dog4 :: Animal
Dog (MkDog {name = "Snowy", age = 4})
>>>
cat ^? _Sub :: Maybe FourLeggedAnimal
Just (Cat4 "Mog" 5)
>>>
duck ^? _Sub :: Maybe FourLeggedAnimal
Nothing
Instances
(Generic sub, Generic sup, GAsSubtype (Rep sub) (Rep sup)) => AsSubtype sub sup | |
Defined in Data.Generics.Sum.Subtype | |
AsSubtype a Void | |
Defined in Data.Generics.Sum.Subtype | |
AsSubtype Void a | |
Defined in Data.Generics.Sum.Subtype |
Cons
class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where #
This class provides a way to attach or detach elements on the left side of a structure in a flexible manner.
Instances
Cons ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons _Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString) # | |
Cons ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons _Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString) # | |
Cons Text Text Char Char | |
Cons Text Text Char Char | |
Cons [a] [b] a b | |
Defined in Control.Lens.Cons | |
Cons (ZipList a) (ZipList b) a b | |
Cons (Seq a) (Seq b) a b | |
(Prim a, Prim b) => Cons (Vector a) (Vector b) a b | |
(Storable a, Storable b) => Cons (Vector a) (Vector b) a b | |
(Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b | |
Cons (Vector a) (Vector b) a b | |
cons :: Cons s s a a => a -> s -> s infixr 5 #
cons
an element onto a container.
>>>
cons a []
[a]
>>>
cons a [b, c]
[a,b,c]
>>>
cons a (Seq.fromList [])
fromList [a]
>>>
cons a (Seq.fromList [b, c])
fromList [a,b,c]
uncons :: Cons s s a a => s -> Maybe (a, s) #
Attempt to extract the left-most element from a container, and a version of the container without that element.
>>>
uncons []
Nothing
>>>
uncons [a, b, c]
Just (a,[b,c])
_head :: Cons s s a a => Traversal' s a #
A Traversal
reading and writing to the head
of a non-empty container.
>>>
[a,b,c]^? _head
Just a
>>>
[a,b,c] & _head .~ d
[d,b,c]
>>>
[a,b,c] & _head %~ f
[f a,b,c]
>>>
[] & _head %~ f
[]
>>>
[1,2,3]^?!_head
1
>>>
[]^?_head
Nothing
>>>
[1,2]^?_head
Just 1
>>>
[] & _head .~ 1
[]
>>>
[0] & _head .~ 2
[2]
>>>
[0,1] & _head .~ 2
[2,1]
This isn't limited to lists.
For instance you can also traverse
the head of a Seq
:
>>>
Seq.fromList [a,b,c,d] & _head %~ f
fromList [f a,b,c,d]
>>>
Seq.fromList [] ^? _head
Nothing
>>>
Seq.fromList [a,b,c,d] ^? _head
Just a
_head
::Traversal'
[a] a_head
::Traversal'
(Seq
a) a_head
::Traversal'
(Vector
a) a
_tail :: Cons s s a a => Traversal' s s #
A Traversal
reading and writing to the tail
of a non-empty container.
>>>
[a,b] & _tail .~ [c,d,e]
[a,c,d,e]
>>>
[] & _tail .~ [a,b]
[]
>>>
[a,b,c,d,e] & _tail.traverse %~ f
[a,f b,f c,f d,f e]
>>>
[1,2] & _tail .~ [3,4,5]
[1,3,4,5]
>>>
[] & _tail .~ [1,2]
[]
>>>
[a,b,c]^?_tail
Just [b,c]
>>>
[1,2]^?!_tail
[2]
>>>
"hello"^._tail
"ello"
>>>
""^._tail
""
This isn't limited to lists. For instance you can also traverse
the tail of a Seq
.
>>>
Seq.fromList [a,b] & _tail .~ Seq.fromList [c,d,e]
fromList [a,c,d,e]
>>>
Seq.fromList [a,b,c] ^? _tail
Just (fromList [b,c])
>>>
Seq.fromList [] ^? _tail
Nothing
_tail
::Traversal'
[a] [a]_tail
::Traversal'
(Seq
a) (Seq
a)_tail
::Traversal'
(Vector
a) (Vector
a)
Snoc
class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where #
This class provides a way to attach or detach elements on the right side of a structure in a flexible manner.
Instances
Snoc ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons _Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8) # | |
Snoc ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons _Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8) # | |
Snoc Text Text Char Char | |
Snoc Text Text Char Char | |
Snoc [a] [b] a b | |
Defined in Control.Lens.Cons | |
Snoc (ZipList a) (ZipList b) a b | |
Snoc (Seq a) (Seq b) a b | |
(Prim a, Prim b) => Snoc (Vector a) (Vector b) a b | |
(Storable a, Storable b) => Snoc (Vector a) (Vector b) a b | |
(Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b | |
Snoc (Vector a) (Vector b) a b | |
snoc :: Snoc s s a a => s -> a -> s infixl 5 #
snoc
an element onto the end of a container.
>>>
snoc (Seq.fromList []) a
fromList [a]
>>>
snoc (Seq.fromList [b, c]) a
fromList [b,c,a]
>>>
snoc (LazyT.pack "hello") '!'
"hello!"
unsnoc :: Snoc s s a a => s -> Maybe (s, a) #
Attempt to extract the right-most element from a container, and a version of the container without that element.
>>>
unsnoc (LazyT.pack "hello!")
Just ("hello",'!')
>>>
unsnoc (LazyT.pack "")
Nothing
>>>
unsnoc (Seq.fromList [b,c,a])
Just (fromList [b,c],a)
>>>
unsnoc (Seq.fromList [])
Nothing
_init :: Snoc s s a a => Traversal' s s #
A Traversal
reading and replacing all but the a last element of a non-empty container.
>>>
[a,b,c,d]^?_init
Just [a,b,c]
>>>
[]^?_init
Nothing
>>>
[a,b] & _init .~ [c,d,e]
[c,d,e,b]
>>>
[] & _init .~ [a,b]
[]
>>>
[a,b,c,d] & _init.traverse %~ f
[f a,f b,f c,d]
>>>
[1,2,3]^?_init
Just [1,2]
>>>
[1,2,3,4]^?!_init
[1,2,3]
>>>
"hello"^._init
"hell"
>>>
""^._init
""
_init
::Traversal'
[a] [a]_init
::Traversal'
(Seq
a) (Seq
a)_init
::Traversal'
(Vector
a) (Vector
a)
_last :: Snoc s s a a => Traversal' s a #
A Traversal
reading and writing to the last element of a non-empty container.
>>>
[a,b,c]^?!_last
c
>>>
[]^?_last
Nothing
>>>
[a,b,c] & _last %~ f
[a,b,f c]
>>>
[1,2]^?_last
Just 2
>>>
[] & _last .~ 1
[]
>>>
[0] & _last .~ 2
[2]
>>>
[0,1] & _last .~ 2
[0,2]
This Traversal
is not limited to lists, however. We can also work with other containers, such as a Vector
.
>>>
Vector.fromList "abcde" ^? _last
Just 'e'
>>>
Vector.empty ^? _last
Nothing
>>>
(Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ"
True
_last
::Traversal'
[a] a_last
::Traversal'
(Seq
a) a_last
::Traversal'
(Vector
a) a