parameterized-utils-1.0.1: Classes and data structures for working with data-kind indexed types

Copyright(c) Galois Inc 2014
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellTrustworthy
LanguageHaskell98

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

Documentation

data HashTable s (key :: k -> *) (val :: k -> *) Source #

A hash table mapping nonces to values.

new :: ST s (HashTable s key val) Source #

Create a new empty table.

newSized :: Int -> ST s (HashTable s k v) Source #

Create a new empty table to hold n elements.

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

hashWithSaltF

Methods

hashWithSaltF :: Int -> f tp -> Int Source #

hashF :: f tp -> Int Source #

Hash with default salt.

Instances
HashableF NatRepr Source # 
Instance details

Defined in Data.Parameterized.NatRepr

Methods

hashWithSaltF :: Int -> NatRepr tp -> Int Source #

hashF :: NatRepr tp -> Int Source #

HashableF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

HashableF (Nonce :: k -> *) Source # 
Instance details

Defined in Data.Parameterized.Nonce.Unsafe

Methods

hashWithSaltF :: Int -> Nonce tp -> Int Source #

hashF :: Nonce tp -> Int Source #

Hashable a => HashableF (Const a :: k -> *) Source # 
Instance details

Defined in Data.Parameterized.Classes

Methods

hashWithSaltF :: Int -> Const a tp -> Int Source #

hashF :: Const a tp -> Int Source #

HashableF (Nonce s :: k -> *) Source # 
Instance details

Defined in Data.Parameterized.Nonce

Methods

hashWithSaltF :: Int -> Nonce s tp -> Int Source #

hashF :: Nonce s tp -> Int Source #

HashableF (Index ctx :: k -> *) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

hashWithSaltF :: Int -> Index ctx tp -> Int Source #

hashF :: Index ctx tp -> Int Source #

HashableF (Index ctx :: k -> *) Source # 
Instance details

Defined in Data.Parameterized.Context.Safe

Methods

hashWithSaltF :: Int -> Index ctx tp -> Int Source #

hashF :: Index ctx tp -> Int Source #

HashableF f => HashableF (Assignment f :: Ctx k -> *) Source # 
Instance details

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 # 
Instance details

Defined in Data.Parameterized.Context.Safe

Methods

hashWithSaltF :: Int -> Assignment f tp -> Int Source #

hashF :: Assignment f tp -> Int Source #

data RealWorld #

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.