optics-extra-0.4: Extra utilities and instances for optics-core
Safe HaskellNone
LanguageHaskell2010

Optics.Cons

Description

This module defines the Cons and Snoc classes, which provide Prisms for the leftmost and rightmost elements of a container, respectively.

Synopsis

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.

Methods

_Cons :: Prism s t (a, s) (b, t) #

_Cons :: Prism [a] [b] (a, [a]) (b, [b])
_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b)
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons :: Prism' String (Char, String)
_Cons :: Prism' Text (Char, Text)
_Cons :: Prism' ByteString (Word8, ByteString)

Instances

Instances details
Cons ByteString ByteString Word8 Word8 Source # 
Instance details

Defined in Optics.Cons

Cons ByteString ByteString Word8 Word8 Source # 
Instance details

Defined in Optics.Cons

Cons Text Text Char Char Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons Text Text Char Char Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons [a] [b] a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism [a] [b] (a, [a]) (b, [b]) #

Cons (ZipList a) (ZipList b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism (ZipList a) (ZipList b) (a, ZipList a) (b, ZipList b) #

Cons (Seq a) (Seq b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b) #

(Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Storable a, Storable b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Prim a, Prim b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

Cons (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(<|) :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

This is an infix alias for cons.

>>> 1 <| []
[1]
>>> 'a' <| "bc"
"abc"
>>> 1 <| []
[1]
>>> 1 <| [2, 3]
[1,2,3]

cons :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

>>> cons 'a' ""
"a"
>>> cons 'a' "bc"
"abc"

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 (:<) :: 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.

Methods

_Snoc :: Prism s t (s, a) (t, b) #

Instances

Instances details
Snoc ByteString ByteString Word8 Word8 Source # 
Instance details

Defined in Optics.Cons

Snoc ByteString ByteString Word8 Word8 Source # 
Instance details

Defined in Optics.Cons

Snoc Text Text Char Char Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc Text Text Char Char Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc [a] [b] a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism [a] [b] ([a], a) ([b], b) #

Snoc (ZipList a) (ZipList b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism (ZipList a) (ZipList b) (ZipList a, a) (ZipList b, b) #

Snoc (Seq a) (Seq b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism (Seq a) (Seq b) (Seq a, a) (Seq b, b) #

(Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Storable a, Storable b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Prim a, Prim b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

Snoc (Vector a) (Vector b) a b Source # 
Instance details

Defined in Optics.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(|>) :: Snoc s s a a => s -> a -> s infixl 5 #

snoc an element onto the end of a container.

This is an infix alias for snoc.

>>> "" |> 'a'
"a"
>>> "bc" |> 'a'
"bca"

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 (:>) :: 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'

Orphan instances

Cons ByteString ByteString Word8 Word8 Source # 
Instance details

Cons ByteString ByteString Word8 Word8 Source # 
Instance details

Cons Text Text Char Char Source # 
Instance details

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons Text Text Char Char Source # 
Instance details

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Snoc ByteString ByteString Word8 Word8 Source # 
Instance details

Snoc ByteString ByteString Word8 Word8 Source # 
Instance details

Snoc Text Text Char Char Source # 
Instance details

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc Text Text Char Char Source # 
Instance details

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

(Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Storable a, Storable b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Prim a, Prim b) => Cons (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

Cons (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Storable a, Storable b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Prim a, Prim b) => Snoc (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

Snoc (Vector a) (Vector b) a b Source # 
Instance details

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #