| Copyright | (c) Galois Inc 2014 | 
|---|---|
| Maintainer | Joe Hendrix <jhendrix@galois.com> | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
Data.Parameterized.HashTable
Description
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 typesafe provided the
 TestEquality instance on the key type is implemented soundly.
Synopsis
- data HashTable s (key :: k -> *) (val :: k -> *)
 - 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 -> *) (val :: k -> *) -> key tp -> val tp -> ST s ()
 - member :: (HashableF key, TestEquality key) => HashTable s (key :: k -> *) (val :: k -> *) -> key (tp :: k) -> ST s Bool
 - delete :: (HashableF key, TestEquality key) => HashTable s (key :: k -> *) (val :: k -> *) -> key (tp :: k) -> ST s ()
 - clear :: (HashableF key, TestEquality key) => HashTable s (key :: k -> *) (val :: k -> *) -> ST s ()
 - class HashableF (f :: k -> *) where
 - data RealWorld
 
Documentation
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 -> *) (val :: k -> *) -> key tp -> val tp -> ST s () Source #
Insert new key and value mapping into table.
member :: (HashableF key, TestEquality key) => HashTable s (key :: k -> *) (val :: k -> *) -> 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 -> *) (val :: k -> *) -> key (tp :: k) -> ST s () Source #
Delete an element from the hash table.
clear :: (HashableF key, TestEquality key) => HashTable s (key :: k -> *) (val :: k -> *) -> ST s () Source #
class HashableF (f :: k -> *) where Source #
A parameterized type that is hashable on all instances.
Minimal complete definition
Instances
| HashableF NatRepr Source # | |
| HashableF SymbolRepr Source # | |
Defined in Data.Parameterized.SymbolRepr  | |
| HashableF (Nonce :: k -> *) Source # | |
| Hashable a => HashableF (Const a :: k -> *) Source # | |
| HashableF (Nonce s :: k -> *) Source # | |
| HashableF (Index ctx :: k -> *) Source # | |
| HashableF (Index ctx :: k -> *) Source # | |
| HashableF f => HashableF (Assignment f :: Ctx k -> *) Source # | |
Defined in Data.Parameterized.Context.Unsafe Methods hashWithSaltF :: Int -> Assignment f tp -> Int Source # hashF :: Assignment f tp -> Int Source #  | |
| HashableF f => HashableF (Assignment f :: Ctx k -> *) Source # | |
Defined in Data.Parameterized.Context.Safe Methods hashWithSaltF :: Int -> Assignment f tp -> Int Source # hashF :: Assignment f tp -> Int Source #  | |