typerep-map-0.5.0.0: Efficient implementation of a dependent map with types as keys
Copyright(c) 2017-2022 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Data.TypeRepMap.Internal

Description

Internal API for TypeRepMap and operations on it. The functions here do not have any stability guarantees and can change between minor versions.

If you need to use this module for purposes other than tests, create an issue.

Synopsis

Documentation

data TypeRepMap (f :: k -> Type) Source #

TypeRepMap is a heterogeneous data structure similar in its essence to Map with types as keys, where each value has the type of its key. In addition to that, each value is wrapped in an interpretation f.

Here is an example of using Maybe as an interpretation, with a comparison to Map:

 Map String (Maybe String)          TypeRepMap Maybe
---------------------------       ---------------------
 "Int"  -> Just "5"                 Int  -> Just 5
 "Bool" -> Just "True"              Bool -> Just True
 "Char" -> Nothing                  Char -> Nothing

The runtime representation of TypeRepMap is an array, not a tree. This makes lookup significantly more efficient.

Constructors

TypeRepMap

an unsafe constructor for TypeRepMap

Fields

Instances

Instances details
IsList (TypeRepMap f) Source #
fromList . toList == 'id'

Creates TypeRepMap from a list of WrapTypeables.

>>> show $ fromList [WrapTypeable $ Identity True, WrapTypeable $ Identity 'a']
TypeRepMap [Bool, Char]
Instance details

Defined in Data.TypeRepMap.Internal

Associated Types

type Item (TypeRepMap f) #

(forall (a :: k). Typeable a => Eq (f a)) => Eq (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

Methods

(==) :: TypeRepMap f -> TypeRepMap f -> Bool #

(/=) :: TypeRepMap f -> TypeRepMap f -> Bool #

Show (TypeRepMap f) Source #

Shows only keys.

Instance details

Defined in Data.TypeRepMap.Internal

Semigroup (TypeRepMap f) Source #

Uses union to combine TypeRepMaps.

Instance details

Defined in Data.TypeRepMap.Internal

Monoid (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

NFData (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

Methods

rnf :: TypeRepMap f -> () #

type Item (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

toFingerprints :: TypeRepMap f -> [Fingerprint] Source #

Returns the list of Fingerprints from TypeRepMap.

empty :: TypeRepMap f Source #

A TypeRepMap with no values stored in it.

size empty == 0
member @a empty == False

one :: forall a f. Typeable a => f a -> TypeRepMap f Source #

Construct a TypeRepMap with a single element.

size (one x) == 1
member @a (one (x :: f a)) == True

insert :: forall a f. Typeable a => f a -> TypeRepMap f -> TypeRepMap f Source #

Insert a value into a TypeRepMap. TypeRepMap optimizes for fast reads rather than inserts, as a trade-off inserts are O(n).

size (insert v tm) >= size tm
member @a (insert (x :: f a) tm) == True

type KindOf (a :: k) = k Source #

type ArgKindOf (f :: k -> l) = k Source #

delete :: forall a (f :: KindOf a -> Type). Typeable a => TypeRepMap f -> TypeRepMap f Source #

Delete a value from a TypeRepMap.

TypeRepMap optimizes for fast reads rather than modifications, as a trade-off deletes are O(n), with an O(log(n)) optimization for when the element is already missing.

size (delete @a tm) <= size tm
member @a (delete @a tm) == False
>>> tm = delete @Bool $ insert (Just True) $ one (Just 'a')
>>> size tm
1
>>> member @Bool tm
False
>>> member @Char tm
True

deleteFirst :: (a -> Bool) -> [a] -> [a] Source #

adjust :: forall a f. Typeable a => (f a -> f a) -> TypeRepMap f -> TypeRepMap f Source #

Update a value at a specific key with the result of the provided function. When the key is not a member of the map, the original map is returned.

>>> trmap = fromList @(TypeRepMap Identity) [WrapTypeable $ Identity "a"]
>>> lookup @String $ adjust (fmap (++ "ww")) trmap
Just (Identity "aww")

alter :: forall a f. Typeable a => (Maybe (f a) -> Maybe (f a)) -> TypeRepMap f -> TypeRepMap f Source #

Updates a value at a specific key, whether or not it exists. This can be used to insert, delete, or update a value of a given type in the map.

>>> func = (\case Nothing -> Just (Identity "new"); Just (Identity s) -> Just (Identity (reverse s)))
>>> lookup @String $ alter func empty
Just (Identity "new")
>>> trmap = fromList @(TypeRepMap Identity) [WrapTypeable $ Identity "helllo"]
>>> lookup @String $ alter func trmap
>>> Just (Identity "olleh")

hoist :: (forall x. f x -> g x) -> TypeRepMap f -> TypeRepMap g Source #

Map over the elements of a TypeRepMap.

>>> tm = insert (Identity True) $ one (Identity 'a')
>>> lookup @Bool tm
Just (Identity True)
>>> lookup @Char tm
Just (Identity 'a')
>>> tm2 = hoist ((:[]) . runIdentity) tm
>>> lookup @Bool tm2
Just [True]
>>> lookup @Char tm2
Just "a"

hoistA :: Applicative t => (forall x. f x -> t (g x)) -> TypeRepMap f -> t (TypeRepMap g) Source #

hoistWithKey :: forall f g. (forall x. Typeable x => f x -> g x) -> TypeRepMap f -> TypeRepMap g Source #

unionWith :: forall f. (forall x. Typeable x => f x -> f x -> f x) -> TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The union of two TypeRepMaps using a combining function for conflicting entries. O(n + m)

union :: TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The (left-biased) union of two TypeRepMaps in O(n + m). It prefers the first map when duplicate keys are encountered, i.e. union == unionWith const.

intersectionWith :: forall f. (forall x. Typeable x => f x -> f x -> f x) -> TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The intersection of two TypeRepMaps using a combining function

O(n + m)

intersection :: TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The intersection of two TypeRepMaps. It keeps all values from the first map whose keys are present in the second.

O(n + m)

member :: forall a (f :: KindOf a -> Type). Typeable a => TypeRepMap f -> Bool Source #

Check if a value of the given type is present in a TypeRepMap.

>>> member @Char $ one (Identity 'a')
True
>>> member @Bool $ one (Identity 'a')
False

lookup :: forall a f. Typeable a => TypeRepMap f -> Maybe (f a) Source #

Lookup a value of the given type in a TypeRepMap.

>>> x = lookup $ insert (Identity (11 :: Int)) empty
>>> x :: Maybe (Identity Int)
Just (Identity 11)
>>> x :: Maybe (Identity ())
Nothing

size :: TypeRepMap f -> Int Source #

Get the amount of elements in a TypeRepMap.

keys :: TypeRepMap f -> [SomeTypeRep] Source #

Return the list of SomeTypeRep from the keys.

keysWith :: (forall (a :: ArgKindOf f). TypeRep a -> r) -> TypeRepMap f -> [r] Source #

Return the list of keys by wrapping them with a user-provided function.

toListWith :: forall f r. (forall (a :: ArgKindOf f). Typeable a => f a -> r) -> TypeRepMap f -> [r] Source #

Return the list of key-value pairs by wrapping them with a user-provided function.

cachedBinarySearch :: Fingerprint -> PrimArray Word64 -> PrimArray Word64 -> Maybe Int Source #

Binary searched based on this article http://bannalia.blogspot.com/2015/06/cache-friendly-binary-search.html with modification for our two-vector search case.

toAny :: f a -> Any Source #

fromAny :: Any -> f a Source #

typeFp :: forall a. Typeable a => Fingerprint Source #

toSortedTriples :: TypeRepMap f -> [(Fingerprint, Any, Any)] Source #

Efficiently get sorted triples from a map in O(n) time

We assume the incoming TypeRepMap is already sorted into cachedBinarySearch order using fromSortedList. Then we can construct the index mapping from the "cached" ordering into monotonically increasing order using generateOrderMapping with the length of the TRM. This takes O(n). We then pull those indexes from the source TRM to get the sorted triples in a total of O(n).

nubByFst :: Eq a => [(a, b, c)] -> [(a, b, c)] Source #

fst3 :: (a, b, c) -> a Source #

data WrapTypeable f where Source #

Existential wrapper around Typeable indexed by f type parameter. Useful for TypeRepMap structure creation form list of WrapTypeables.

Constructors

WrapTypeable :: Typeable a => f a -> WrapTypeable f 

Instances

Instances details
Show (WrapTypeable f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

calcFp :: forall a. Typeable a => Fingerprint Source #

fromSortedList :: forall a. [a] -> [a] Source #

invariantCheck :: TypeRepMap f -> Bool Source #

Check that invariant of the structure holds. The structure maintains the following invariant. For each element A at index i:

  1. if there is an element B at index 2*i+1, then B < A.
  2. if there is an element C at index 2*i+2, then A < C.