{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RecordWildCards #-}
module Database.Franz.Contents
  ( Contents
  , Database.Franz.Internal.Contents.indexNames
  , Item(..)
  , toList
  , toVector
  , last
  , length
  , index
  , lookupIndex
  ) where

import qualified Data.ByteString.Char8 as B
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
import Database.Franz.Internal.Protocol
import Database.Franz.Internal.Contents
import Data.Int
import Prelude hiding (length, last)

data Item = Item
  { Item -> Int
seqNo :: !Int
  , Item -> Vector Int64
indices :: !(U.Vector Int64)
  , Item -> ByteString
payload :: !B.ByteString
  } deriving (Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
(Int -> Item -> ShowS)
-> (Item -> String) -> ([Item] -> ShowS) -> Show Item
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Item] -> ShowS
$cshowList :: [Item] -> ShowS
show :: Item -> String
$cshow :: Item -> String
showsPrec :: Int -> Item -> ShowS
$cshowsPrec :: Int -> Item -> ShowS
Show, Item -> Item -> Bool
(Item -> Item -> Bool) -> (Item -> Item -> Bool) -> Eq Item
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Item -> Item -> Bool
$c/= :: Item -> Item -> Bool
== :: Item -> Item -> Bool
$c== :: Item -> Item -> Bool
Eq)

toList :: Contents -> [Item]
toList :: Contents -> [Item]
toList Contents
contents = [Contents -> Int -> Item
unsafeIndex Contents
contents Int
i | Int
i <- [Int
0..Contents -> Int
length Contents
contents Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]]

toVector :: Contents -> V.Vector Item
toVector :: Contents -> Vector Item
toVector Contents
contents = Int -> (Int -> Item) -> Vector Item
forall a. Int -> (Int -> a) -> Vector a
V.generate (Contents -> Int
length Contents
contents) (Contents -> Int -> Item
unsafeIndex Contents
contents)

last :: Contents -> Maybe Item
last :: Contents -> Maybe Item
last Contents
contents
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = Item -> Maybe Item
forall a. a -> Maybe a
Just (Item -> Maybe Item) -> Item -> Maybe Item
forall a b. (a -> b) -> a -> b
$ Contents -> Int -> Item
unsafeIndex Contents
contents Int
i
  | Bool
otherwise = Maybe Item
forall a. Maybe a
Nothing
  where
    i :: Int
i = Contents -> Int
length Contents
contents Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1

index :: Contents -> Int -> Maybe Item
index :: Contents -> Int -> Maybe Item
index Contents
contents Int
i
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Contents -> Int
length Contents
contents Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = Maybe Item
forall a. Maybe a
Nothing
  | Bool
otherwise = Item -> Maybe Item
forall a. a -> Maybe a
Just (Item -> Maybe Item) -> Item -> Maybe Item
forall a b. (a -> b) -> a -> b
$ Contents -> Int -> Item
unsafeIndex Contents
contents Int
i

unsafeIndex :: Contents -> Int -> Item
unsafeIndex :: Contents -> Int -> Item
unsafeIndex Contents{Int
ByteString
IndexVec
Vector ByteString
seqnoOffset :: Contents -> Int
payloadOffset :: Contents -> Int
indicess :: Contents -> IndexVec
payloads :: Contents -> ByteString
seqnoOffset :: Int
payloadOffset :: Int
length :: Int
indicess :: IndexVec
payloads :: ByteString
indexNames :: Vector ByteString
length :: Contents -> Int
indexNames :: Contents -> Vector ByteString
..} Int
i = Item :: Int -> Vector Int64 -> ByteString -> Item
Item{Int
ByteString
Vector Int64
payload :: ByteString
seqNo :: Int
indices :: Vector Int64
payload :: ByteString
indices :: Vector Int64
seqNo :: Int
..}
  where
    ofs0 :: Int
ofs0 = Int
-> ((Int, Vector Int64) -> Int) -> Maybe (Int, Vector Int64) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
payloadOffset (Int, Vector Int64) -> Int
forall a b. (a, b) -> a
fst (Maybe (Int, Vector Int64) -> Int)
-> Maybe (Int, Vector Int64) -> Int
forall a b. (a -> b) -> a -> b
$ IndexVec
indicess IndexVec -> Int -> Maybe (Int, Vector Int64)
forall a. Vector a -> Int -> Maybe a
V.!? (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    (Int
ofs1, Vector Int64
indices) = IndexVec
indicess IndexVec -> Int -> (Int, Vector Int64)
forall a. Vector a -> Int -> a
V.! Int
i
    seqNo :: Int
seqNo = Int
seqnoOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
    payload :: ByteString
payload = Int -> ByteString -> ByteString
B.take (Int
ofs1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ofs0) (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
B.drop (Int
ofs0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
payloadOffset) ByteString
payloads

lookupIndex :: Contents -> IndexName -> Maybe (Item -> Int64)
lookupIndex :: Contents -> ByteString -> Maybe (Item -> Int64)
lookupIndex Contents{Vector ByteString
indexNames :: Vector ByteString
indexNames :: Contents -> Vector ByteString
indexNames} ByteString
name
  = (\Int
j Item{Vector Int64
indices :: Vector Int64
indices :: Item -> Vector Int64
indices} -> Vector Int64
indices Vector Int64 -> Int -> Int64
forall a. Unbox a => Vector a -> Int -> a
U.! Int
j) (Int -> Item -> Int64) -> Maybe Int -> Maybe (Item -> Int64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Vector ByteString -> Maybe Int
forall a. Eq a => a -> Vector a -> Maybe Int
V.elemIndex ByteString
name Vector ByteString
indexNames