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)
data Deque = Deque
{ Deque -> [ByteString]
front :: [S.ByteString]
, Deque -> [ByteString]
rear :: [S.ByteString]
,
Deque -> Int64
byteLength :: !Int64
}
empty :: Deque
empty :: Deque
empty = [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [] [] Int64
0
null :: Deque -> Bool
null :: Deque -> Bool
null Deque
deque = Deque -> Int64
byteLength Deque
deque Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
0
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 ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
fs) [ByteString]
rs (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ ByteString -> Int64
len ByteString
x)
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 ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
rs) (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ ByteString -> Int64
len ByteString
x)
len :: S.ByteString -> Int64
len :: ByteString -> Int64
len ByteString
x = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
S.length ByteString
x
popFront :: Deque -> Maybe (S.ByteString, Deque)
popFront :: Deque -> Maybe (ByteString, Deque)
popFront (Deque [] [ByteString]
rs Int64
acc) = case [ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
rs of
[] -> Maybe (ByteString, Deque)
forall a. Maybe a
Nothing
ByteString
x : [ByteString]
xs -> (ByteString, Deque) -> Maybe (ByteString, Deque)
forall a. a -> Maybe a
Just (ByteString
x, [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
xs [] (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x))
popFront (Deque (ByteString
x : [ByteString]
xs) [ByteString]
rs Int64
acc) = (ByteString, Deque) -> Maybe (ByteString, Deque)
forall a. a -> Maybe a
Just (ByteString
x, [ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
xs [ByteString]
rs (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x))
popRear :: Deque -> Maybe (Deque, S.ByteString)
popRear :: Deque -> Maybe (Deque, ByteString)
popRear (Deque [ByteString]
fs [] Int64
acc) = case [ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
fs of
[] -> Maybe (Deque, ByteString)
forall a. Maybe a
Nothing
ByteString
x : [ByteString]
xs -> (Deque, ByteString) -> Maybe (Deque, ByteString)
forall a. a -> Maybe a
Just ([ByteString] -> [ByteString] -> Int64 -> Deque
Deque [] [ByteString]
xs (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x), ByteString
x)
popRear (Deque [ByteString]
fs (ByteString
x : [ByteString]
xs) Int64
acc) = (Deque, ByteString) -> Maybe (Deque, ByteString)
forall a. a -> Maybe a
Just ([ByteString] -> [ByteString] -> Int64 -> Deque
Deque [ByteString]
fs [ByteString]
xs (Int64
acc Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- ByteString -> Int64
len ByteString
x), ByteString
x)