indexation-0.8: Tools for entity indexation

Safe HaskellNone
LanguageHaskell2010

Indexation.Data

Synopsis

Documentation

lookupEntity :: Index entity -> EntityTable entity -> Maybe entity Source #

lookupIndex :: (Eq entity, Hashable entity) => entity -> IndexTable entity -> Maybe (Index entity) Source #

createIndexSet :: (Eq entity, Hashable entity, Foldable foldable) => IndexTable entity -> foldable entity -> IndexSet entity Source #

lookupInIndexSet :: Index entity -> IndexSet entity -> Bool Source #

lookupNewIndex :: Index entity -> ReindexTable entity -> Maybe (Index entity) Source #

uniteIndexSets :: [IndexSet entity] -> IndexSet entity Source #

data Indexer entity Source #

Constructors

Indexer !(TVar Int) !(Map entity Int) 

data IndexTable entity Source #

Constructors

IndexTable !Int !(HashMap entity Int) 
Instances
(Serialize entity, Eq entity, Hashable entity) => Serialize (IndexTable entity) # 
Instance details

Defined in Indexation.Instances.Cereal

Methods

put :: Putter (IndexTable entity) #

get :: Get (IndexTable entity) #

newtype ReindexTable entity Source #

Map from old to new indices.

Constructors

ReindexTable (Vector (Maybe Int)) 

newtype EntityTable entity Source #

Constructors

EntityTable (Vector entity) 
Instances
Serialize entity => Serialize (EntityTable entity) # 
Instance details

Defined in Indexation.Instances.Cereal

Methods

put :: Putter (EntityTable entity) #

get :: Get (EntityTable entity) #

newtype Index entity Source #

Constructors

Index Int 
Instances
Vector Vector (Maybe (Index a)) # 
Instance details

Defined in Indexation.Instances

Vector Vector (Index a) # 
Instance details

Defined in Indexation.Instances

MVector MVector (Maybe (Index a)) # 
Instance details

Defined in Indexation.Instances

MVector MVector (Index a) # 
Instance details

Defined in Indexation.Instances

Eq (Index a) # 
Instance details

Defined in Indexation.Instances

Methods

(==) :: Index a -> Index a -> Bool #

(/=) :: Index a -> Index a -> Bool #

Ord (Index a) # 
Instance details

Defined in Indexation.Instances

Methods

compare :: Index a -> Index a -> Ordering #

(<) :: Index a -> Index a -> Bool #

(<=) :: Index a -> Index a -> Bool #

(>) :: Index a -> Index a -> Bool #

(>=) :: Index a -> Index a -> Bool #

max :: Index a -> Index a -> Index a #

min :: Index a -> Index a -> Index a #

Show (Index a) # 
Instance details

Defined in Indexation.Instances

Methods

showsPrec :: Int -> Index a -> ShowS #

show :: Index a -> String #

showList :: [Index a] -> ShowS #

Generic (Index a) # 
Instance details

Defined in Indexation.Instances

Associated Types

type Rep (Index a) :: * -> * #

Methods

from :: Index a -> Rep (Index a) x #

to :: Rep (Index a) x -> Index a #

Unbox (Maybe (Index a)) # 
Instance details

Defined in Indexation.Instances

Unbox (Index a) # 
Instance details

Defined in Indexation.Instances

Serialize (Index a) # 
Instance details

Defined in Indexation.Instances.Cereal

Methods

put :: Putter (Index a) #

get :: Get (Index a) #

NFData (Index a) # 
Instance details

Defined in Indexation.Instances

Methods

rnf :: Index a -> () #

Hashable (Index a) # 
Instance details

Defined in Indexation.Instances

Methods

hashWithSalt :: Int -> Index a -> Int #

hash :: Index a -> Int #

data MVector s (Index a) # 
Instance details

Defined in Indexation.Instances

data MVector s (Index a) = MV_Index (MVector s Int)
data MVector s (Maybe (Index a)) # 
Instance details

Defined in Indexation.Instances

data MVector s (Maybe (Index a)) = MV_MaybeIndex (MVector s (Bit, Index a))
type Rep (Index a) # 
Instance details

Defined in Indexation.Instances

type Rep (Index a) = D1 (MetaData "Index" "Indexation.Types" "indexation-0.8-1dMieAKnF9T9Y4wUpUAmK5" True) (C1 (MetaCons "Index" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (Maybe (Index a)) # 
Instance details

Defined in Indexation.Instances

data Vector (Index a) # 
Instance details

Defined in Indexation.Instances

newtype IndexSet entity Source #

Set of indices. A more efficient alternative to HashSet (Index entity).

Constructors

IndexSet DenseIntSet 
Instances
Show (IndexSet a) # 
Instance details

Defined in Indexation.Instances

Methods

showsPrec :: Int -> IndexSet a -> ShowS #

show :: IndexSet a -> String #

showList :: [IndexSet a] -> ShowS #

Serialize (IndexSet a) # 
Instance details

Defined in Indexation.Instances.Cereal

Methods

put :: Putter (IndexSet a) #

get :: Get (IndexSet a) #

newtype IndexCounts entity Source #

Constructors

IndexCounts (Vector Word32) 
Instances
Serialize (IndexCounts a) # 
Instance details

Defined in Indexation.Instances.Cereal

Methods

put :: Putter (IndexCounts a) #

get :: Get (IndexCounts a) #