| Portability | non-portable | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Trustworthy | 
Control.Lens.Cons
Description
- class (Profunctor p, Functor f) => Cons p f s t a b | s -> a, t -> b, s b -> t, t a -> s where- _Cons :: Overloaded p f s t (a, s) (b, t)
 
- (<|) :: Cons Reviewed Identity s s a a => a -> s -> s
- cons :: Cons Reviewed Identity s s a a => a -> s -> s
- uncons :: Cons (->) (Accessor (First (a, s))) s s a a => s -> Maybe (a, s)
- _head :: Cons (->) f s s a a => LensLike' f s a
- _tail :: Cons (->) f s s a a => LensLike' f s s
- class (Profunctor p, Functor f) => Snoc p f s t a b | s -> a, t -> b, s b -> t, t a -> s where- _Snoc :: Overloaded p f s t (s, a) (t, b)
 
- (|>) :: Snoc Reviewed Identity s s a a => s -> a -> s
- snoc :: Snoc Reviewed Identity s s a a => s -> a -> s
- unsnoc :: Snoc (->) (Accessor (First (s, a))) s s a a => s -> Maybe (s, a)
- _init :: Snoc (->) f s s a a => LensLike' f s s
- _last :: Snoc (->) f s s a a => LensLike' f s a
Cons
class (Profunctor p, Functor f) => Cons p f s t a b | s -> a, t -> b, s b -> t, t a -> s whereSource
This class provides a way to attach or detach elements on the left side of a structure in a flexible manner.
Methods
_Cons :: Overloaded p f s t (a, s) (b, t)Source
Most of the time this is a Prism.
_Cons::Prism[a] [b] (a, [a]) (b, [b])_Cons::Prism(Seqa) (Seqb) (a,Seqa) (b,Seqb)_Cons::Prism(Vectora) (Vectorb) (a,Vectora) (b,Vectorb)_Cons::Prism'String(Char,String)_Cons::Prism'Text(Char,Text)_Cons::Prism'ByteString(Word8,ByteString)
However, by including p and f in the class you can write instances that only permit uncons
 or which only permit cons, or where _head and _tail are lenses and not traversals.
Instances
| (Choice p, Applicative f) => Cons p f Text Text Char Char | |
| (Choice p, Applicative f) => Cons p f Text Text Char Char | |
| (Choice p, Applicative f) => Cons p f ByteString ByteString Word8 Word8 | |
| (Choice p, Applicative f) => Cons p f ByteString ByteString Word8 Word8 | |
| (Choice p, Applicative f, Unbox a, Unbox b) => Cons p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f, Storable a, Storable b) => Cons p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f, Prim a, Prim b) => Cons p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f) => Cons p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f) => Cons p f (Seq a) (Seq b) a b | |
| (Choice p, Applicative f) => Cons p f [a] [b] a b | |
| (Choice p, Applicative f) => Cons p f (Deque a) (Deque b) a b | 
uncons :: Cons (->) (Accessor (First (a, s))) s s a a => s -> Maybe (a, s)Source
Attempt to extract the left-most element from a container, and a version of the container without that element.
_head :: Cons (->) f s s a a => LensLike' f s aSource
A Traversal reading and writing to the head of a non-empty container.
>>>[a,b,c]^? _headJust a
>>>[a,b,c] & _head .~ d[d,b,c]
>>>[a,b,c] & _head %~ f[f a,b,c]
>>>[] & _head %~ f[]
>>>[1,2,3]^?!_head1
>>>[]^?_headNothing
>>>[1,2]^?_headJust 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 %~ ffromList [f a,b,c,d]
>>>Seq.fromList [] ^? _headNothing
>>>Seq.fromList [a,b,c,d] ^? _headJust a
_head::Traversal'[a] a_head::Traversal'(Seqa) a_head::Traversal'(Vectora) a
_tail :: Cons (->) f s s a a => LensLike' f s sSource
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]^?_tailJust [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] ^? _tailJust (fromList [b,c])
>>>Seq.fromList [] ^? _tailNothing
_tail::Traversal'[a] [a]_tail::Traversal'(Seqa) (Seqa)_tail::Traversal'(Vectora) (Vectora)
Snoc
class (Profunctor p, Functor f) => Snoc p f s t a b | s -> a, t -> b, s b -> t, t a -> s whereSource
This class provides a way to attach or detach elements on the right side of a structure in a flexible manner.
Methods
_Snoc :: Overloaded p f s t (s, a) (t, b)Source
Most of the time this is a Prism.
_Snoc::Prism[a] [b] ([a], a) ([b], b)_Snoc::Prism(Seqa) (Seqb) (Seqa, a) (Seqb, b)_Snoc::Prism(Vectora) (Vectorb) (Vectora, a) (Vectorb, b)_Snoc::Prism'String(String,Char)_Snoc::Prism'Text(Text,Char)_Snoc::Prism'ByteString(ByteString,Word8)
However, by including p and f in the class you can write instances that only permit unsnoc
 or which only permit snoc or where _init and _last are lenses and not traversals.
Instances
| (Choice p, Applicative f) => Snoc p f Text Text Char Char | |
| (Choice p, Applicative f) => Snoc p f Text Text Char Char | |
| (Choice p, Applicative f) => Snoc p f ByteString ByteString Word8 Word8 | |
| (Choice p, Applicative f) => Snoc p f ByteString ByteString Word8 Word8 | |
| (Choice p, Applicative f, Unbox a, Unbox b) => Snoc p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f, Storable a, Storable b) => Snoc p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f, Prim a, Prim b) => Snoc p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f) => Snoc p f (Vector a) (Vector b) a b | |
| (Choice p, Applicative f) => Snoc p f (Seq a) (Seq b) a b | |
| (Choice p, Applicative f) => Snoc p f [a] [b] a b | |
| (Choice p, Applicative f) => Snoc p f (Deque a) (Deque b) a b | 
snoc :: Snoc Reviewed Identity s s a a => s -> a -> sSource
snoc an element onto the end of a container.
unsnoc :: Snoc (->) (Accessor (First (s, a))) s s a a => s -> Maybe (s, a)Source
Attempt to extract the right-most element from a container, and a version of the container without that element.
_init :: Snoc (->) f s s a a => LensLike' f s sSource
A Traversal reading and replacing all but the a last element of a non-empty container.
>>>[a,b,c,d]^?_initJust [a,b,c]
>>>[]^?_initNothing
>>>[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]^?_initJust [1,2]
>>>[1,2,3,4]^?!_init[1,2,3]
>>>"hello"^._init"hell"
>>>""^._init""
_init::Traversal'[a] [a]_init::Traversal'(Seqa) (Seqa)_init::Traversal'(Vectora) (Vectora)
_last :: Snoc (->) f s s a a => LensLike' f s aSource
A Traversal reading and writing to the last element of a non-empty container.
>>>[a,b,c]^?!_lastc
>>>[]^?_lastNothing
>>>[a,b,c] & _last %~ f[a,b,f c]
>>>[1,2]^?_lastJust 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" ^? _lastJust 'e'
>>>Vector.empty ^? _lastNothing
>>>Vector.fromList "abcde" & _last .~ 'Q'fromList "abcdQ"
_last::Traversal'[a] a_last::Traversal'(Seqa) a_last::Traversal'(Vectora) a