{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
module Data.ByteString.Strict.Lens
  ( packedBytes, unpackedBytes, bytes
  , packedChars, unpackedChars, chars
  , pattern Bytes
  , pattern Chars
  ) where
import Control.Lens
import Control.Lens.Internal.ByteString
import Data.ByteString (ByteString)
import qualified Data.ByteString       as Words
import qualified Data.ByteString.Char8 as Char8
import Data.Word
packedBytes :: Iso' [Word8] ByteString
packedBytes :: p ByteString (f ByteString) -> p [Word8] (f [Word8])
packedBytes = ([Word8] -> ByteString)
-> (ByteString -> [Word8])
-> Iso [Word8] [Word8] ByteString 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 :: p [Word8] (f [Word8]) -> p ByteString (f ByteString)
unpackedBytes = AnIso [Word8] [Word8] ByteString ByteString
-> Iso ByteString ByteString [Word8] [Word8]
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso [Word8] [Word8] ByteString ByteString
Iso [Word8] [Word8] ByteString ByteString
packedBytes
{-# INLINE unpackedBytes #-}
bytes :: IndexedTraversal' Int ByteString Word8
bytes :: p Word8 (f Word8) -> ByteString -> f ByteString
bytes = p Word8 (f Word8) -> ByteString -> f ByteString
IndexedTraversal' Int ByteString Word8
traversedStrictTree
{-# INLINE bytes #-}
packedChars :: Iso' String ByteString
packedChars :: p ByteString (f ByteString) -> p String (f String)
packedChars = (String -> ByteString)
-> (ByteString -> String)
-> Iso String String ByteString 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 :: p String (f String) -> p ByteString (f ByteString)
unpackedChars = AnIso String String ByteString ByteString
-> Iso ByteString ByteString String String
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso String String ByteString ByteString
Iso String String ByteString ByteString
packedChars
{-# INLINE unpackedChars #-}
chars :: IndexedTraversal' Int ByteString Char
chars :: p Char (f Char) -> ByteString -> f ByteString
chars = p Char (f Char) -> ByteString -> f ByteString
IndexedTraversal' Int ByteString Char
traversedStrictTree8
{-# 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 = AReview ByteString [Word8] -> [Word8] -> ByteString
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ByteString [Word8]
Iso ByteString ByteString [Word8] [Word8]
unpackedBytes [Word8]
b
pattern Chars :: String -> ByteString
pattern $bChars :: String -> ByteString
$mChars :: forall r. ByteString -> (String -> r) -> (Void# -> r) -> r
Chars b <- (view unpackedChars -> b) where
  Chars String
b = AReview ByteString String -> String -> ByteString
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ByteString String
Iso ByteString ByteString String String
unpackedChars String
b