| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Optic.Prism.Cons
Contents
Synopsis
- 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
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.
Minimal complete definition
Methods
Instances
| Cons ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons Methods _Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString) # | |
| Cons ByteString ByteString Word8 Word8 | |
Defined in Control.Lens.Cons Methods _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]^? _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 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]^?_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)