{- |
 A Deque used for accumulating `S.ByteString`s in `Data.ByteString.Lazy.dropEnd`.
-}
module Data.ByteString.Lazy.Internal.Deque (
    Deque (..),
    empty,
    null,
    cons,
    snoc,
    popFront,
    popRear,
) where

import qualified Data.ByteString as S
import Data.Int (Int64)
import Prelude hiding (head, length, null)

-- A `S.ByteString` Deque used as an accumulator for lazy
-- Bytestring operations
data Deque = Deque
    { Deque -> [ByteString]
front :: [S.ByteString]
    , Deque -> [ByteString]
rear :: [S.ByteString]
    , -- | Total length in bytes
      Deque -> Int64
byteLength :: !Int64
    }

-- An empty Deque
empty :: Deque
empty :: Deque
empty = [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [] [] Int64
0

-- Is the `Deque` empty?
-- O(1)
null :: Deque -> Bool
null :: Deque -> Bool
null Deque
deque = Deque -> Int64
byteLength Deque
deque forall a. Eq a => a -> a -> Bool
== Int64
0

-- Add a `S.ByteString` to the front of the `Deque`
-- O(1)
cons :: S.ByteString -> Deque -> Deque
cons :: ByteString -> Deque -> Deque
cons ByteString
x (Deque [ByteString]
fs [ByteString]
rs Int64
acc) = [ByteString] -> [ByteString] -> Int64 -> Deque
Deque (ByteString
x forall a. a -> [a] -> [a]
: [ByteString]
fs) [ByteString]
rs (Int64
acc forall a. Num a => a -> a -> a
+ ByteString -> Int64
len ByteString
x)

-- Add a `S.ByteString` to the rear of the `Deque`
-- O(1)
snoc :: S.ByteString -> Deque -> Deque
snoc :: ByteString -> Deque -> Deque
snoc ByteString
x (Deque [ByteString]
fs [ByteString]
rs Int64
acc) = [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
fs (ByteString
x forall a. a -> [a] -> [a]
: [ByteString]
rs) (Int64
acc forall a. Num a => a -> a -> a
+ ByteString -> Int64
len ByteString
x)

len :: S.ByteString -> Int64
len :: ByteString -> Int64
len ByteString
x = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
S.length ByteString
x

-- Pop a `S.ByteString` from the front of the `Deque`
-- Returns the bytestring and the updated Deque, or Nothing if the Deque is empty
-- O(1) , occasionally O(n)
popFront :: Deque -> Maybe (S.ByteString, Deque)
popFront :: Deque -> Maybe (ByteString, Deque)
popFront (Deque [] [ByteString]
rs Int64
acc) = case forall a. [a] -> [a]
reverse [ByteString]
rs of
    [] -> forall a. Maybe a
Nothing
    ByteString
x : [ByteString]
xs -> forall a. a -> Maybe a
Just (ByteString
x, [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
xs [] (Int64
acc forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x))
popFront (Deque (ByteString
x : [ByteString]
xs) [ByteString]
rs Int64
acc) = forall a. a -> Maybe a
Just (ByteString
x, [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
xs [ByteString]
rs (Int64
acc forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x))

-- Pop a `S.ByteString` from the rear of the `Deque`
-- Returns the bytestring and the updated Deque, or Nothing if the Deque is empty
-- O(1) , occasionally O(n)
popRear :: Deque -> Maybe (Deque, S.ByteString)
popRear :: Deque -> Maybe (Deque, ByteString)
popRear (Deque [ByteString]
fs [] Int64
acc) = case forall a. [a] -> [a]
reverse [ByteString]
fs of
    [] -> forall a. Maybe a
Nothing
    ByteString
x : [ByteString]
xs -> forall a. a -> Maybe a
Just ([ByteString] -> [ByteString] -> Int64 -> Deque
Deque [] [ByteString]
xs (Int64
acc forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x), ByteString
x)
popRear (Deque [ByteString]
fs (ByteString
x : [ByteString]
xs) Int64
acc) = forall a. a -> Maybe a
Just ([ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
fs [ByteString]
xs (Int64
acc forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x), ByteString
x)