{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Optics.Cons
(
Cons(..)
, (<|)
, cons
, uncons
, _head, _tail
, pattern (:<)
, Snoc(..)
, (|>)
, snoc
, unsnoc
, _init, _last
, pattern (:>)
) where
import Data.Vector (Vector)
import Data.Vector.Primitive (Prim)
import Data.Vector.Storable (Storable)
import Data.Vector.Unboxed (Unbox)
import Data.Word (Word8)
import qualified Data.ByteString as StrictB
import qualified Data.ByteString.Lazy as LazyB
import qualified Data.Text as StrictT
import qualified Data.Text.Lazy as LazyT
import qualified Data.Vector as Vector
import qualified Data.Vector.Primitive as Prim
import qualified Data.Vector.Storable as Storable
import qualified Data.Vector.Unboxed as Unbox
import Optics.Core
import Optics.Internal.Utils
instance Cons StrictB.ByteString StrictB.ByteString Word8 Word8 where
_Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString)
_Cons = ((Word8, ByteString) -> ByteString)
-> (ByteString -> Maybe (Word8, ByteString))
-> Prism
ByteString ByteString (Word8, ByteString) (Word8, ByteString)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ((Word8 -> ByteString -> ByteString)
-> (Word8, ByteString) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Word8 -> ByteString -> ByteString
StrictB.cons) ByteString -> Maybe (Word8, ByteString)
StrictB.uncons
{-# INLINE _Cons #-}
instance Cons LazyB.ByteString LazyB.ByteString Word8 Word8 where
_Cons :: Prism ByteString ByteString (Word8, ByteString) (Word8, ByteString)
_Cons = ((Word8, ByteString) -> ByteString)
-> (ByteString -> Maybe (Word8, ByteString))
-> Prism
ByteString ByteString (Word8, ByteString) (Word8, ByteString)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ((Word8 -> ByteString -> ByteString)
-> (Word8, ByteString) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Word8 -> ByteString -> ByteString
LazyB.cons) ByteString -> Maybe (Word8, ByteString)
LazyB.uncons
{-# INLINE _Cons #-}
instance Cons StrictT.Text StrictT.Text Char Char where
_Cons :: Prism Text Text (Char, Text) (Char, Text)
_Cons = ((Char, Text) -> Text)
-> (Text -> Maybe (Char, Text))
-> Prism Text Text (Char, Text) (Char, Text)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ((Char -> Text -> Text) -> (Char, Text) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Char -> Text -> Text
StrictT.cons) Text -> Maybe (Char, Text)
StrictT.uncons
{-# INLINE _Cons #-}
instance Cons LazyT.Text LazyT.Text Char Char where
_Cons :: Prism Text Text (Char, Text) (Char, Text)
_Cons = ((Char, Text) -> Text)
-> (Text -> Maybe (Char, Text))
-> Prism Text Text (Char, Text) (Char, Text)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ((Char -> Text -> Text) -> (Char, Text) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Char -> Text -> Text
LazyT.cons) Text -> Maybe (Char, Text)
LazyT.uncons
{-# INLINE _Cons #-}
instance Cons (Vector a) (Vector b) a b where
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons = ((b, Vector b) -> Vector b)
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((b -> Vector b -> Vector b) -> (b, Vector b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' b -> Vector b -> Vector b
forall a. a -> Vector a -> Vector a
Vector.cons) ((Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b))
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v ->
if Vector a -> Bool
forall a. Vector a -> Bool
Vector.null Vector a
v
then Vector b -> Either (Vector b) (a, Vector a)
forall a b. a -> Either a b
Left Vector b
forall a. Vector a
Vector.empty
else (a, Vector a) -> Either (Vector b) (a, Vector a)
forall a b. b -> Either a b
Right (Vector a -> a
forall a. Vector a -> a
Vector.unsafeHead Vector a
v, Vector a -> Vector a
forall a. Vector a -> Vector a
Vector.unsafeTail Vector a
v)
{-# INLINE _Cons #-}
instance (Prim a, Prim b) => Cons (Prim.Vector a) (Prim.Vector b) a b where
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons = ((b, Vector b) -> Vector b)
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((b -> Vector b -> Vector b) -> (b, Vector b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' b -> Vector b -> Vector b
forall a. Prim a => a -> Vector a -> Vector a
Prim.cons) ((Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b))
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v ->
if Vector a -> Bool
forall a. Prim a => Vector a -> Bool
Prim.null Vector a
v
then Vector b -> Either (Vector b) (a, Vector a)
forall a b. a -> Either a b
Left Vector b
forall a. Prim a => Vector a
Prim.empty
else (a, Vector a) -> Either (Vector b) (a, Vector a)
forall a b. b -> Either a b
Right (Vector a -> a
forall a. Prim a => Vector a -> a
Prim.unsafeHead Vector a
v, Vector a -> Vector a
forall a. Prim a => Vector a -> Vector a
Prim.unsafeTail Vector a
v)
{-# INLINE _Cons #-}
instance (Storable a, Storable b) => Cons (Storable.Vector a) (Storable.Vector b) a b where
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons = ((b, Vector b) -> Vector b)
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((b -> Vector b -> Vector b) -> (b, Vector b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' b -> Vector b -> Vector b
forall a. Storable a => a -> Vector a -> Vector a
Storable.cons) ((Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b))
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v ->
if Vector a -> Bool
forall a. Storable a => Vector a -> Bool
Storable.null Vector a
v
then Vector b -> Either (Vector b) (a, Vector a)
forall a b. a -> Either a b
Left Vector b
forall a. Storable a => Vector a
Storable.empty
else (a, Vector a) -> Either (Vector b) (a, Vector a)
forall a b. b -> Either a b
Right (Vector a -> a
forall a. Storable a => Vector a -> a
Storable.unsafeHead Vector a
v, Vector a -> Vector a
forall a. Storable a => Vector a -> Vector a
Storable.unsafeTail Vector a
v)
{-# INLINE _Cons #-}
instance (Unbox a, Unbox b) => Cons (Unbox.Vector a) (Unbox.Vector b) a b where
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons = ((b, Vector b) -> Vector b)
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((b -> Vector b -> Vector b) -> (b, Vector b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' b -> Vector b -> Vector b
forall a. Unbox a => a -> Vector a -> Vector a
Unbox.cons) ((Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b))
-> (Vector a -> Either (Vector b) (a, Vector a))
-> Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v ->
if Vector a -> Bool
forall a. Unbox a => Vector a -> Bool
Unbox.null Vector a
v
then Vector b -> Either (Vector b) (a, Vector a)
forall a b. a -> Either a b
Left Vector b
forall a. Unbox a => Vector a
Unbox.empty
else (a, Vector a) -> Either (Vector b) (a, Vector a)
forall a b. b -> Either a b
Right (Vector a -> a
forall a. Unbox a => Vector a -> a
Unbox.unsafeHead Vector a
v, Vector a -> Vector a
forall a. Unbox a => Vector a -> Vector a
Unbox.unsafeTail Vector a
v)
{-# INLINE _Cons #-}
instance Snoc (Vector a) (Vector b) a b where
_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
_Snoc = ((Vector b, b) -> Vector b)
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Vector b -> b -> Vector b) -> (Vector b, b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Vector b -> b -> Vector b
forall a. Vector a -> a -> Vector a
Vector.snoc) ((Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b))
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v -> if Vector a -> Bool
forall a. Vector a -> Bool
Vector.null Vector a
v
then Vector b -> Either (Vector b) (Vector a, a)
forall a b. a -> Either a b
Left Vector b
forall a. Vector a
Vector.empty
else (Vector a, a) -> Either (Vector b) (Vector a, a)
forall a b. b -> Either a b
Right (Vector a -> Vector a
forall a. Vector a -> Vector a
Vector.unsafeInit Vector a
v, Vector a -> a
forall a. Vector a -> a
Vector.unsafeLast Vector a
v)
{-# INLINE _Snoc #-}
instance (Prim a, Prim b) => Snoc (Prim.Vector a) (Prim.Vector b) a b where
_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
_Snoc = ((Vector b, b) -> Vector b)
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Vector b -> b -> Vector b) -> (Vector b, b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Vector b -> b -> Vector b
forall a. Prim a => Vector a -> a -> Vector a
Prim.snoc) ((Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b))
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v -> if Vector a -> Bool
forall a. Prim a => Vector a -> Bool
Prim.null Vector a
v
then Vector b -> Either (Vector b) (Vector a, a)
forall a b. a -> Either a b
Left Vector b
forall a. Prim a => Vector a
Prim.empty
else (Vector a, a) -> Either (Vector b) (Vector a, a)
forall a b. b -> Either a b
Right (Vector a -> Vector a
forall a. Prim a => Vector a -> Vector a
Prim.unsafeInit Vector a
v, Vector a -> a
forall a. Prim a => Vector a -> a
Prim.unsafeLast Vector a
v)
{-# INLINE _Snoc #-}
instance (Storable a, Storable b) => Snoc (Storable.Vector a) (Storable.Vector b) a b where
_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
_Snoc = ((Vector b, b) -> Vector b)
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Vector b -> b -> Vector b) -> (Vector b, b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Vector b -> b -> Vector b
forall a. Storable a => Vector a -> a -> Vector a
Storable.snoc) ((Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b))
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v -> if Vector a -> Bool
forall a. Storable a => Vector a -> Bool
Storable.null Vector a
v
then Vector b -> Either (Vector b) (Vector a, a)
forall a b. a -> Either a b
Left Vector b
forall a. Storable a => Vector a
Storable.empty
else (Vector a, a) -> Either (Vector b) (Vector a, a)
forall a b. b -> Either a b
Right (Vector a -> Vector a
forall a. Storable a => Vector a -> Vector a
Storable.unsafeInit Vector a
v, Vector a -> a
forall a. Storable a => Vector a -> a
Storable.unsafeLast Vector a
v)
{-# INLINE _Snoc #-}
instance (Unbox a, Unbox b) => Snoc (Unbox.Vector a) (Unbox.Vector b) a b where
_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
_Snoc = ((Vector b, b) -> Vector b)
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Vector b -> b -> Vector b) -> (Vector b, b) -> Vector b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Vector b -> b -> Vector b
forall a. Unbox a => Vector a -> a -> Vector a
Unbox.snoc) ((Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b))
-> (Vector a -> Either (Vector b) (Vector a, a))
-> Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
forall a b. (a -> b) -> a -> b
$ \Vector a
v -> if Vector a -> Bool
forall a. Unbox a => Vector a -> Bool
Unbox.null Vector a
v
then Vector b -> Either (Vector b) (Vector a, a)
forall a b. a -> Either a b
Left Vector b
forall a. Unbox a => Vector a
Unbox.empty
else (Vector a, a) -> Either (Vector b) (Vector a, a)
forall a b. b -> Either a b
Right (Vector a -> Vector a
forall a. Unbox a => Vector a -> Vector a
Unbox.unsafeInit Vector a
v, Vector a -> a
forall a. Unbox a => Vector a -> a
Unbox.unsafeLast Vector a
v)
{-# INLINE _Snoc #-}
instance Snoc StrictB.ByteString StrictB.ByteString Word8 Word8 where
_Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8)
_Snoc = ((ByteString, Word8) -> ByteString)
-> (ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((ByteString -> Word8 -> ByteString)
-> (ByteString, Word8) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' ByteString -> Word8 -> ByteString
StrictB.snoc) ((ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8))
-> (ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8)
forall a b. (a -> b) -> a -> b
$ \ByteString
v -> if ByteString -> Bool
StrictB.null ByteString
v
then ByteString -> Either ByteString (ByteString, Word8)
forall a b. a -> Either a b
Left ByteString
StrictB.empty
else (ByteString, Word8) -> Either ByteString (ByteString, Word8)
forall a b. b -> Either a b
Right (ByteString -> ByteString
StrictB.init ByteString
v, ByteString -> Word8
StrictB.last ByteString
v)
{-# INLINE _Snoc #-}
instance Snoc LazyB.ByteString LazyB.ByteString Word8 Word8 where
_Snoc :: Prism ByteString ByteString (ByteString, Word8) (ByteString, Word8)
_Snoc = ((ByteString, Word8) -> ByteString)
-> (ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((ByteString -> Word8 -> ByteString)
-> (ByteString, Word8) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' ByteString -> Word8 -> ByteString
LazyB.snoc) ((ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8))
-> (ByteString -> Either ByteString (ByteString, Word8))
-> Prism
ByteString ByteString (ByteString, Word8) (ByteString, Word8)
forall a b. (a -> b) -> a -> b
$ \ByteString
v -> if ByteString -> Bool
LazyB.null ByteString
v
then ByteString -> Either ByteString (ByteString, Word8)
forall a b. a -> Either a b
Left ByteString
LazyB.empty
else (ByteString, Word8) -> Either ByteString (ByteString, Word8)
forall a b. b -> Either a b
Right (ByteString -> ByteString
LazyB.init ByteString
v, ByteString -> Word8
LazyB.last ByteString
v)
{-# INLINE _Snoc #-}
instance Snoc StrictT.Text StrictT.Text Char Char where
_Snoc :: Prism Text Text (Text, Char) (Text, Char)
_Snoc = ((Text, Char) -> Text)
-> (Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Text -> Char -> Text) -> (Text, Char) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Text -> Char -> Text
StrictT.snoc) ((Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char))
-> (Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char)
forall a b. (a -> b) -> a -> b
$ \Text
v -> if Text -> Bool
StrictT.null Text
v
then Text -> Either Text (Text, Char)
forall a b. a -> Either a b
Left Text
StrictT.empty
else (Text, Char) -> Either Text (Text, Char)
forall a b. b -> Either a b
Right (Text -> Text
StrictT.init Text
v, Text -> Char
StrictT.last Text
v)
{-# INLINE _Snoc #-}
instance Snoc LazyT.Text LazyT.Text Char Char where
_Snoc :: Prism Text Text (Text, Char) (Text, Char)
_Snoc = ((Text, Char) -> Text)
-> (Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ((Text -> Char -> Text) -> (Text, Char) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' Text -> Char -> Text
LazyT.snoc) ((Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char))
-> (Text -> Either Text (Text, Char))
-> Prism Text Text (Text, Char) (Text, Char)
forall a b. (a -> b) -> a -> b
$ \Text
v -> if Text -> Bool
LazyT.null Text
v
then Text -> Either Text (Text, Char)
forall a b. a -> Either a b
Left Text
LazyT.empty
else (Text, Char) -> Either Text (Text, Char)
forall a b. b -> Either a b
Right (Text -> Text
LazyT.init Text
v, Text -> Char
LazyT.last Text
v)
{-# INLINE _Snoc #-}