module Data.Identifiers
( Identifiers ()
, empty
, fromList
, insert
, insertMany
, size
, toList
, lookupId
, lookupKey
, lookupKeys
, unsafeLookupId
, unsafeLookupKey
, (!)
, prop_hasId
, prop_stableId
, prop_keyRetrieval
, prop_keyRetrievalUnsafe
, prop_idempotent
) where
import Control.Applicative hiding (empty)
import Control.DeepSeq
import Data.Binary
import Data.List (foldl')
import Data.Hashable
import Data.HashMap.Lazy (HashMap)
import Data.Maybe
import Data.Sequence (Seq, (|>))
import Data.Serialize (Serialize)
import qualified Data.HashMap.Lazy as H
import qualified Data.Sequence as S
import qualified Data.Serialize as C
data Identifiers i a = Identifiers { ids :: !(HashMap a i)
, names :: !(Seq a)
} deriving Eq
instance Show a => Show (Identifiers i a) where
show s = "insertMany empty " ++ show (H.keys (ids s))
instance (Binary i, Eq a, Hashable a, Binary a) => Binary (Identifiers i a) where
put s = put (H.toList $ ids s) >> put (names s)
get = Identifiers <$> (H.fromList <$> get) <*> get
instance (Serialize i, Eq a, Hashable a, Serialize a) => Serialize (Identifiers i a) where
put s = C.put (H.toList $ ids s) >> C.put (names s)
get = Identifiers <$> (H.fromList <$> C.get) <*> C.get
instance (NFData i, NFData a) => NFData (Identifiers i a) where
rnf (Identifiers i n) = rnf (i, n)
empty :: Identifiers i a
empty = Identifiers H.empty S.empty
fromList :: (Integral i, Hashable a, Eq a) => [a] -> Identifiers i a
fromList = insertMany empty
insert :: (Integral i, Hashable a, Eq a) => Identifiers i a -> a -> Identifiers i a
insert xs v = case H.lookup v (ids xs) of
Just _ -> xs
Nothing -> Identifiers (H.insert v next $ ids xs) (names xs |> v)
where next = fromIntegral $ S.length $ names xs
insertMany :: (Integral i, Hashable a, Eq a) => Identifiers i a -> [a] -> Identifiers i a
insertMany = foldl' insert
toList :: Identifiers i a -> [a]
toList = H.keys . ids
lookupId :: (Hashable a, Eq a) => Identifiers i a -> a -> Maybe i
lookupId = flip H.lookup . ids
size :: Identifiers i a -> Int
size = S.length . names
unsafeLookupId :: (Hashable a, Eq a) => Identifiers i a -> a -> i
unsafeLookupId = (H.!) . ids
lookupKey :: (Integral i) => Identifiers i a -> i -> Maybe a
lookupKey ident x = let xs = names ident
in if S.length xs < fromIntegral x
then Nothing
else Just $ unsafeLookupKey ident x
lookupKeys :: (Integral i) => Identifiers i a -> [i] -> [a]
lookupKeys s = mapMaybe (lookupKey s)
unsafeLookupKey :: Integral i => Identifiers i a -> i -> a
unsafeLookupKey xs x = S.index (names xs) (fromIntegral x)
(!) :: Integral i => Identifiers i a -> i -> a
(!) = unsafeLookupKey
prop_hasId :: String -> Bool
prop_hasId x = isJust . lookupId (insert (empty :: Identifiers Int String) x) $ x
prop_stableId :: String -> Bool
prop_stableId x = isJust a && a == b
where a = lookupId firstSet x
b = lookupId secondSet x
firstSet = insert (empty :: Identifiers Int String) x
secondSet = insert firstSet x
prop_keyRetrievalUnsafe :: [String] -> Bool
prop_keyRetrievalUnsafe xs = all (\x -> ret x == x) xs
where ret = unsafeLookupKey s . unsafeLookupId s
s = insertMany (empty :: Identifiers Int String) xs
prop_keyRetrieval :: [String] -> Bool
prop_keyRetrieval xs = all (\x -> ret x == Just (Just x)) xs
where ret x = lookupKey s <$> lookupId s x
s = insertMany (empty :: Identifiers Int String) xs
prop_idempotent :: String -> Bool
prop_idempotent x = insert (empty :: Identifiers Int String) x
== insert (insert empty x) x