{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
module Data.ByteString.Lazy.Optics
  ( packedBytes, unpackedBytes, bytes
  , packedChars, unpackedChars, chars
  , pattern Bytes
  , pattern Chars
  ) where
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy       as Words
import qualified Data.ByteString.Lazy.Char8 as Char8
import Data.Int (Int64)
import Data.Word (Word8)
import Optics.Core
import Optics.Extra.Internal.ByteString
packedBytes :: Iso' [Word8] ByteString
packedBytes :: Iso' [Word8] ByteString
packedBytes = ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> Iso' [Word8] ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso [Word8] -> ByteString
Words.pack ByteString -> [Word8]
Words.unpack
{-# INLINE packedBytes #-}
unpackedBytes :: Iso' ByteString [Word8]
unpackedBytes :: Iso' ByteString [Word8]
unpackedBytes = Iso' [Word8] ByteString
-> Optic
     (ReversedOptic An_Iso) NoIx ByteString ByteString [Word8] [Word8]
forall k (is :: IxList) s t a b.
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Iso' [Word8] ByteString
packedBytes
{-# INLINE unpackedBytes #-}
bytes :: IxTraversal' Int64 ByteString Word8
bytes :: IxTraversal' Int64 ByteString Word8
bytes = IxTraversal' Int64 ByteString Word8
traversedLazy
{-# INLINE bytes #-}
packedChars :: Iso' String ByteString
packedChars :: Iso' String ByteString
packedChars = (String -> ByteString)
-> (ByteString -> String) -> Iso' String ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso String -> ByteString
Char8.pack ByteString -> String
Char8.unpack
{-# INLINE packedChars #-}
unpackedChars :: Iso' ByteString String
unpackedChars :: Iso' ByteString String
unpackedChars = Iso' String ByteString
-> Optic
     (ReversedOptic An_Iso) NoIx ByteString ByteString String String
forall k (is :: IxList) s t a b.
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Iso' String ByteString
packedChars
{-# INLINE unpackedChars #-}
chars :: IxTraversal' Int64 ByteString Char
chars :: IxTraversal' Int64 ByteString Char
chars = IxTraversal' Int64 ByteString Char
traversedLazy8
{-# INLINE chars #-}
pattern Bytes :: [Word8] -> ByteString
pattern $bBytes :: [Word8] -> ByteString
$mBytes :: forall r. ByteString -> ([Word8] -> r) -> (Void# -> r) -> r
Bytes b <- (view unpackedBytes -> b) where
  Bytes [Word8]
b = Iso' ByteString [Word8] -> [Word8] -> ByteString
forall k (is :: IxList) t b.
Is k A_Review =>
Optic' k is t b -> b -> t
review Iso' ByteString [Word8]
unpackedBytes [Word8]
b
pattern Chars :: [Char] -> ByteString
pattern $bChars :: String -> ByteString
$mChars :: forall r. ByteString -> (String -> r) -> (Void# -> r) -> r
Chars b <- (view unpackedChars -> b) where
  Chars String
b = Iso' ByteString String -> String -> ByteString
forall k (is :: IxList) t b.
Is k A_Review =>
Optic' k is t b -> b -> t
review Iso' ByteString String
unpackedChars String
b