Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 => AffineTraversal' s a
- _tail :: Cons s s a a => AffineTraversal' s s
- pattern (:<) :: forall s a. Cons s s a a => a -> s -> s
- 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 => AffineTraversal' s s
- _last :: Snoc s s a a => AffineTraversal' s a
- pattern (:>) :: forall s a. Snoc s s a a => s -> a -> s
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 Source # | |
Defined in Optics.Cons _Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString) # | |
Cons ByteString ByteString Word8 Word8 Source # | |
Defined in Optics.Cons _Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString) # | |
Cons Text Text Char Char Source # | |
Cons Text Text Char Char Source # | |
Cons [a] [b] a b | |
Defined in Optics.Cons.Core | |
Cons (ZipList a) (ZipList b) a b | |
Cons (Seq a) (Seq b) a b | |
(Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b Source # | |
(Storable a, Storable b) => Cons (Vector a) (Vector b) a b Source # | |
(Prim a, Prim b) => Cons (Vector a) (Vector b) a b Source # | |
Cons (Vector a) (Vector b) a b Source # | |
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 [1, 2, 3]
Just (1,[2,3])
_head :: Cons s s a a => AffineTraversal' s a #
An AffineTraversal
reading and writing to the head
of a non-empty
container.
>>>
"abc" ^? _head
Just 'a'
>>>
"abc" & _head .~ 'd'
"dbc"
>>>
[1,2,3] & _head %~ (*10)
[10,2,3]
>>>
[] & _head %~ absurd
[]
>>>
[1,2,3] ^? _head
Just 1
>>>
[] ^? _head
Nothing
>>>
[1,2] ^? _head
Just 1
>>>
[] & _head .~ 1
[]
>>>
[0] & _head .~ 2
[2]
>>>
[0,1] & _head .~ 2
[2,1]
_tail :: Cons s s a a => AffineTraversal' s s #
An AffineTraversal
reading and writing to the tail
of a non-empty
container.
>>>
"ab" & _tail .~ "cde"
"acde"
>>>
[] & _tail .~ [1,2]
[]
>>>
[1,2,3,4,5] & _tail % traversed %~ (*10)
[1,20,30,40,50]
>>>
[1,2] & _tail .~ [3,4,5]
[1,3,4,5]
>>>
[] & _tail .~ [1,2]
[]
>>>
"abc" ^? _tail
Just "bc"
>>>
"hello" ^? _tail
Just "ello"
>>>
"" ^? _tail
Nothing
pattern (:<) :: forall s a. Cons s s a a => a -> s -> s infixr 5 #
Pattern synonym for matching on the leftmost element of a structure.
>>>
case ['a','b','c'] of (x :< _) -> x
'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 Source # | |
Defined in Optics.Cons _Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8) # | |
Snoc ByteString ByteString Word8 Word8 Source # | |
Defined in Optics.Cons _Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8) # | |
Snoc Text Text Char Char Source # | |
Snoc Text Text Char Char Source # | |
Snoc [a] [b] a b | |
Defined in Optics.Cons.Core | |
Snoc (ZipList a) (ZipList b) a b | |
Snoc (Seq a) (Seq b) a b | |
(Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b Source # | |
(Storable a, Storable b) => Snoc (Vector a) (Vector b) a b Source # | |
(Prim a, Prim b) => Snoc (Vector a) (Vector b) a b Source # | |
Snoc (Vector a) (Vector b) a b Source # | |
snoc :: Snoc s s a a => s -> a -> s infixl 5 #
snoc
an element onto the end of a container.
>>>
snoc "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 "hello!"
Just ("hello",'!')
>>>
unsnoc ""
Nothing
_init :: Snoc s s a a => AffineTraversal' s s #
An AffineTraversal
reading and replacing all but the a last element of a
non-empty container.
>>>
"abcd" ^? _init
Just "abc"
>>>
"" ^? _init
Nothing
>>>
"ab" & _init .~ "cde"
"cdeb"
>>>
[] & _init .~ [1,2]
[]
>>>
[1,2,3,4] & _init % traversed %~ (*10)
[10,20,30,4]
>>>
[1,2,3] ^? _init
Just [1,2]
>>>
"hello" ^? _init
Just "hell"
>>>
[] ^? _init
Nothing
_last :: Snoc s s a a => AffineTraversal' s a #
An AffineTraversal
reading and writing to the last element of a
non-empty container.
>>>
"abc" ^? _last
Just 'c'
>>>
"" ^? _last
Nothing
>>>
[1,2,3] & _last %~ (+1)
[1,2,4]
>>>
[1,2] ^? _last
Just 2
>>>
[] & _last .~ 1
[]
>>>
[0] & _last .~ 2
[2]
>>>
[0,1] & _last .~ 2
[0,2]
pattern (:>) :: forall s a. Snoc s s a a => s -> a -> s infixl 5 #
Pattern synonym for matching on the rightmost element of a structure.
>>>
case ['a','b','c'] of (_ :> x) -> x
'c'