parameterized-utils-2.1.6.0: Classes and data structures for working with data-kind indexed types
Copyright(c) Galois Inc 2014-2019
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellTrustworthy
LanguageHaskell2010

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 type-safe provided that the TestEquality instance on the key type is implemented soundly.

Synopsis

Documentation

data HashTable s (key :: k -> Type) (val :: k -> Type) 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 -> 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.

Minimal complete definition

hashWithSaltF

Methods

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

hashF :: f tp -> Int Source #

Hash with default salt.

Instances

Instances details
HashableF NatRepr Source # 
Instance details

Defined in Data.Parameterized.NatRepr.Internal

Methods

hashWithSaltF :: forall (tp :: k). Int -> NatRepr tp -> Int Source #

hashF :: forall (tp :: k). NatRepr tp -> Int Source #

HashableF PeanoRepr Source # 
Instance details

Defined in Data.Parameterized.Peano

Methods

hashWithSaltF :: forall (tp :: k). Int -> PeanoRepr tp -> Int Source #

hashF :: forall (tp :: k). PeanoRepr tp -> Int Source #

HashableF BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

hashWithSaltF :: forall (tp :: k). Int -> BoolRepr tp -> Int Source #

hashF :: forall (tp :: k). BoolRepr tp -> Int Source #

HashableF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

hashWithSaltF :: forall (tp :: k). Int -> SymbolRepr tp -> Int Source #

hashF :: forall (tp :: k). SymbolRepr tp -> Int Source #

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

Defined in Data.Parameterized.Nonce.Unsafe

Methods

hashWithSaltF :: forall (tp :: k0). Int -> Nonce tp -> Int Source #

hashF :: forall (tp :: k0). Nonce tp -> Int Source #

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

Defined in Data.Parameterized.Classes

Methods

hashWithSaltF :: forall (tp :: k0). Int -> Const a tp -> Int Source #

hashF :: forall (tp :: k0). Const a tp -> Int Source #

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

Defined in Data.Parameterized.Context.Unsafe

Methods

hashWithSaltF :: forall (tp :: k0). Int -> Index ctx tp -> Int Source #

hashF :: forall (tp :: k0). Index ctx tp -> Int Source #

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

Defined in Data.Parameterized.Nonce

Methods

hashWithSaltF :: forall (tp :: k0). Int -> Nonce s tp -> Int Source #

hashF :: forall (tp :: k0). Nonce s tp -> Int Source #

(HashableF f, TestEquality f) => HashableF (Assignment f :: Ctx k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

hashWithSaltF :: forall (tp :: k0). Int -> Assignment f tp -> Int Source #

hashF :: forall (tp :: k0). 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#.