Copyright | (c) Galois Inc 2014-2019 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module provides a ST
-based hashtable for parameterized keys and values.
NOTE: This API makes use of unsafeCoerce
to implement the parameterized
hashtable abstraction. This should be type-safe provided that the
TestEquality
instance on the key type is implemented soundly.
Synopsis
- data HashTable s (key :: k -> Type) (val :: k -> Type)
- new :: ST s (HashTable s key val)
- newSized :: Int -> ST s (HashTable s k v)
- clone :: (HashableF key, TestEquality key) => HashTable s key val -> ST s (HashTable s key val)
- lookup :: (HashableF key, TestEquality key) => HashTable s key val -> key tp -> ST s (Maybe (val tp))
- insert :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key tp -> val tp -> ST s ()
- member :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key (tp :: k) -> ST s Bool
- delete :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key (tp :: k) -> ST s ()
- clear :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> ST s ()
- class HashableF (f :: k -> Type) where
- hashWithSaltF :: Int -> f tp -> Int
- hashF :: f tp -> Int
- data RealWorld
Documentation
data HashTable s (key :: k -> Type) (val :: k -> Type) Source #
A hash table mapping nonces to values.
clone :: (HashableF key, TestEquality key) => HashTable s key val -> ST s (HashTable s key val) Source #
Create a hash table that is a copy of the current one.
lookup :: (HashableF key, TestEquality key) => HashTable s key val -> key tp -> ST s (Maybe (val tp)) Source #
Lookup value of key in table.
insert :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key tp -> val tp -> ST s () Source #
Insert new key and value mapping into table.
member :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key (tp :: k) -> ST s Bool Source #
Return true if the key is in the hash table.
delete :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> key (tp :: k) -> ST s () Source #
Delete an element from the hash table.
clear :: (HashableF key, TestEquality key) => HashTable s (key :: k -> Type) (val :: k -> Type) -> ST s () Source #
class HashableF (f :: k -> Type) where Source #
A parameterized type that is hashable on all instances.
Instances
HashableF NatRepr Source # | |
HashableF PeanoRepr Source # | |
HashableF BoolRepr Source # | |
HashableF SymbolRepr Source # | |
Defined in Data.Parameterized.SymbolRepr hashWithSaltF :: forall (tp :: k). Int -> SymbolRepr tp -> Int Source # hashF :: forall (tp :: k). SymbolRepr tp -> Int Source # | |
HashableF (Nonce :: k -> Type) Source # | |
Hashable a => HashableF (Const a :: k -> Type) Source # | |
HashableF (Index ctx :: k -> Type) Source # | |
HashableF (Nonce s :: k -> Type) Source # | |
(HashableF f, TestEquality f) => HashableF (Assignment f :: Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe hashWithSaltF :: forall (tp :: k0). Int -> Assignment f tp -> Int Source # hashF :: forall (tp :: k0). Assignment f tp -> Int Source # |