module Data.ByteString.Optics
  ( IsByteString(..)
  , unpackedBytes
  , unpackedChars
  , pattern Bytes
  , pattern Chars
  ) where

import qualified Data.ByteString as Strict
import qualified Data.ByteString.Lazy as Lazy
import Data.Int (Int64)
import Data.Word (Word8)
import qualified Data.ByteString.Lazy.Optics as Lazy
import qualified Data.ByteString.Strict.Optics as Strict

import Optics.Core

-- | Traversals for ByteStrings.
class IsByteString t where
  -- | 'Data.ByteString.pack' (or 'Data.ByteString.unpack') a list of bytes into
  -- a strict or lazy 'ByteString'.
  --
  -- @
  -- 'Data.ByteString.pack' x ≡ x '^.' 'packedBytes'
  -- 'Data.ByteString.unpack' x ≡ x '^.' 're' 'packedBytes'
  -- 'packedBytes' ≡ 're' 'unpackedBytes'
  -- @
  packedBytes :: Iso' [Word8] t

  -- | 'Data.ByteString.Char8.pack' (or 'Data.ByteString.Char8.unpack') a list
  -- of characters into a strict or lazy 'ByteString'.
  --
  -- When writing back to the 'ByteString' it is assumed that every 'Char' lies
  -- between @'\x00'@ and @'\xff'@.
  --
  -- @
  -- 'Data.ByteString.Char8.pack' x ≡ x '^.' 'packedChars'
  -- 'Data.ByteString.Char8.unpack' x ≡ x '^.' 're' 'packedChars'
  -- 'packedChars' ≡ 're' 'unpackedChars'
  -- @
  packedChars :: Iso' String t

  -- | Traverse each 'Word8' in a strict or lazy 'ByteString'
  --
  --
  -- This 'Traversal' walks each strict 'ByteString' chunk in a tree-like
  -- fashion enable zippers to seek to locations more quickly and accelerate
  -- many monoidal queries, but up to associativity (and constant factors) it is
  -- equivalent to the much slower:
  --
  -- @
  -- 'bytes' ≡ 'unpackedBytes' '.' 'traversed'
  -- @
  --
  -- @
  -- 'anyOf' 'bytes' ('==' 0x80) :: 'ByteString' -> 'Bool'
  -- @
  bytes :: IxTraversal' Int64 t Word8

  -- | Traverse the individual bytes in a strict or lazy 'ByteString' as
  -- characters.
  --
  -- When writing back to the 'ByteString' it is assumed that every 'Char' lies
  -- between @'\x00'@ and @'\xff'@.
  --
  -- This 'Traversal' walks each strict 'ByteString' chunk in a tree-like
  -- fashion enable zippers to seek to locations more quickly and accelerate
  -- many monoidal queries, but up to associativity (and constant factors) it is
  -- equivalent to the much slower:
  --
  -- @
  -- 'chars' ≡ 'unpackedChars' '.' 'traversed'
  -- @
  --
  -- @
  -- 'anyOf' 'chars' ('==' \'c\') :: 'ByteString' -> 'Bool'
  -- @
  chars :: IxTraversal' Int64 t Char

-- | 'Data.ByteString.unpack' (or 'Data.ByteString.pack') a 'ByteString' into a
-- list of bytes.
--
-- @
-- 'unpackedBytes' ≡ 're' 'packedBytes'
-- 'Data.ByteString.unpack' x ≡ x '^.' 'unpackedBytes'
-- 'Data.ByteString.pack' x ≡  x '^.' 're' 'unpackedBytes'
-- @
--
-- @
-- 'unpackedBytes' :: 'Iso'' 'Data.ByteString.ByteString' ['Word8']
-- 'unpackedBytes' :: 'Iso'' 'Data.ByteString.Lazy.ByteString' ['Word8']
-- @
unpackedBytes :: IsByteString t => Iso' t [Word8]
unpackedBytes :: Iso' t [Word8]
unpackedBytes = Optic An_Iso NoIx [Word8] [Word8] t t
-> Optic (ReversedOptic An_Iso) NoIx t t [Word8] [Word8]
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
       (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Optic An_Iso NoIx [Word8] [Word8] t t
forall (t :: OpticKind). IsByteString t => Iso' [Word8] t
packedBytes
{-# INLINE unpackedBytes #-}

pattern Bytes :: IsByteString t => [Word8] -> t
pattern $bBytes :: [Word8] -> t
$mBytes :: forall r (t :: OpticKind).
IsByteString t =>
t -> ([Word8] -> r) -> (Void# -> r) -> r
Bytes b <- (view unpackedBytes -> b) where
  Bytes [Word8]
b = Optic' An_Iso NoIx t [Word8] -> [Word8] -> t
forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
review Optic' An_Iso NoIx t [Word8]
forall (t :: OpticKind). IsByteString t => Iso' t [Word8]
unpackedBytes [Word8]
b

pattern Chars :: IsByteString t => [Char] -> t
pattern $bChars :: [Char] -> t
$mChars :: forall r (t :: OpticKind).
IsByteString t =>
t -> ([Char] -> r) -> (Void# -> r) -> r
Chars b <- (view unpackedChars -> b) where
  Chars [Char]
b = Optic' An_Iso NoIx t [Char] -> [Char] -> t
forall (k :: OpticKind) (is :: IxList) (t :: OpticKind)
       (b :: OpticKind).
Is k A_Review =>
Optic' k is t b -> b -> t
review Optic' An_Iso NoIx t [Char]
forall (t :: OpticKind). IsByteString t => Iso' t [Char]
unpackedChars [Char]
b

-- | 'Data.ByteString.Char8.unpack' (or 'Data.ByteString.Char8.pack') a list of
-- characters into a strict (or lazy) 'ByteString'
--
-- When writing back to the 'ByteString' it is assumed that every 'Char' lies
-- between @'\x00'@ and @'\xff'@.
--
-- @
-- 'unpackedChars' ≡ 're' 'packedChars'
-- 'Data.ByteString.Char8.unpack' x ≡ x '^.' 'unpackedChars'
-- 'Data.ByteString.Char8.pack' x ≡ x '^.' 're' 'unpackedChars'
-- @
--
-- @
-- 'unpackedChars' :: 'Iso'' 'Data.ByteString.ByteString' 'String'
-- 'unpackedChars' :: 'Iso'' 'Data.ByteString.Lazy.ByteString' 'String'
-- @
unpackedChars :: IsByteString t => Iso' t String
unpackedChars :: Iso' t [Char]
unpackedChars = Optic An_Iso NoIx [Char] [Char] t t
-> Optic (ReversedOptic An_Iso) NoIx t t [Char] [Char]
forall (k :: OpticKind) (is :: IxList) (s :: OpticKind)
       (t :: OpticKind) (a :: OpticKind) (b :: OpticKind).
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Optic An_Iso NoIx [Char] [Char] t t
forall (t :: OpticKind). IsByteString t => Iso' [Char] t
packedChars
{-# INLINE unpackedChars #-}

instance IsByteString Strict.ByteString where
  packedBytes :: Iso' [Word8] ByteString
packedBytes = Iso' [Word8] ByteString
Strict.packedBytes
  packedChars :: Iso' [Char] ByteString
packedChars = Iso' [Char] ByteString
Strict.packedChars
  bytes :: IxTraversal' Int64 ByteString Word8
bytes       = IxTraversal' Int64 ByteString Word8
Strict.bytes
  chars :: IxTraversal' Int64 ByteString Char
chars       = IxTraversal' Int64 ByteString Char
Strict.chars
  {-# INLINE packedBytes #-}
  {-# INLINE packedChars #-}
  {-# INLINE bytes #-}
  {-# INLINE chars #-}

instance IsByteString Lazy.ByteString where
  packedBytes :: Iso' [Word8] ByteString
packedBytes = Iso' [Word8] ByteString
Lazy.packedBytes
  packedChars :: Iso' [Char] ByteString
packedChars = Iso' [Char] ByteString
Lazy.packedChars
  bytes :: IxTraversal' Int64 ByteString Word8
bytes       = IxTraversal' Int64 ByteString Word8
Lazy.bytes
  chars :: IxTraversal' Int64 ByteString Char
chars       = IxTraversal' Int64 ByteString Char
Lazy.chars
  {-# INLINE packedBytes #-}
  {-# INLINE packedChars #-}
  {-# INLINE bytes #-}
  {-# INLINE chars #-}