hashcons-0.1.0: Hash-consing and memoisation

Copyright© 2018 Andy Morris
LicenseBSD-3-Clause
Maintainerhello@andy-morris.xyz
Stabilityexperimental
PortabilityGHC internals; weak pointers & finalizers; stable names
Safe HaskellNone
LanguageHaskell2010

Data.HashCons

Description

Hash-consing, or interning, is a way to gain constant-time equality testing (and hashing) for potentially-large data types such as strings or abstract syntax trees. Internally a table of live values is kept, and newly-constructed values are looked up in the table to check if they already exist. If they do, then the existing one is reused (along with a tag). The table is pruned using finalisers when these tagged values are garbage collected.

This library should be thread- and exception-safe.

Synopsis

Documentation

class (Eq a, Hashable a) => HashCons a Source #

Types which support hash-consing.

There are some restrictions on types for which this class makes sense:

  1. The type must have no type variables: an instance for T Int would be fine, but not for T a. (There must also be no constraints, but that is unlikely to be a problem if all instances are ground.)
  2. Equality and hashing must consider all data in a value. It need not necessarily be structural equality, but a subterm should not simply be ignored. (An example of why someone might want to ave equality ignore parts of a type is annotations in an abstract syntax tree.)

Instances

HashCons Integer Source # 

Methods

hcCache :: Cache Integer

HashCons Natural Source # 

Methods

hcCache :: Cache Natural

HashCons ByteString Source # 

Methods

hcCache :: Cache ByteString

HashCons ByteString Source # 

Methods

hcCache :: Cache ByteString

HashCons Text Source # 

Methods

hcCache :: Cache Text

HashCons Text Source # 

Methods

hcCache :: Cache Text

HashCons [Char] Source # 

Methods

hcCache :: Cache [Char]

hc :: HashCons a => a -> HC a Source #

Make a hash-consed value.

data HC a Source #

A value which has been given a unique tag.

Instances

Eq (HC a) Source #

\(\mathcal{O}(1)\) using the tag

Methods

(==) :: HC a -> HC a -> Bool #

(/=) :: HC a -> HC a -> Bool #

Ord a => Ord (HC a) Source #

Checks the tag for equality first, and otherwise falls back to the underlying type's ordering

Methods

compare :: HC a -> HC a -> Ordering #

(<) :: HC a -> HC a -> Bool #

(<=) :: HC a -> HC a -> Bool #

(>) :: HC a -> HC a -> Bool #

(>=) :: HC a -> HC a -> Bool #

max :: HC a -> HC a -> HC a #

min :: HC a -> HC a -> HC a #

(Read a, HashCons a) => Read (HC a) Source #

Reads an underlying value and caches it

Show a => Show (HC a) Source #

Shows the underlying value

Methods

showsPrec :: Int -> HC a -> ShowS #

show :: HC a -> String #

showList :: [HC a] -> ShowS #

(Storable a, HashCons a) => Storable (HC a) Source #

Stores the underlying value, and re-caches it on retrieval

Methods

sizeOf :: HC a -> Int #

alignment :: HC a -> Int #

peekElemOff :: Ptr (HC a) -> Int -> IO (HC a) #

pokeElemOff :: Ptr (HC a) -> Int -> HC a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (HC a) #

pokeByteOff :: Ptr b -> Int -> HC a -> IO () #

peek :: Ptr (HC a) -> IO (HC a) #

poke :: Ptr (HC a) -> HC a -> IO () #

NFData a => NFData (HC a) Source #

Also evaluates the underlying value

Methods

rnf :: HC a -> () #

MkWeak (HC a) Source # 

Methods

mkWeak :: HC a -> v -> Maybe Finalizer -> IO (Weak v) Source #

mkWeakPtr :: HC a -> Maybe Finalizer -> IO (Weak (HC a)) Source #

addFinalizer :: HC a -> Finalizer -> IO () Source #

Hashable (HC a) Source #

\(\mathcal{O}(1)\) using the tag

Methods

hashWithSalt :: Int -> HC a -> Int #

hash :: HC a -> Int #

MemoArg (HC a) Source # 

Associated Types

type Key (HC a) :: Type Source #

type CanFinalize (HC a) :: Bool Source #

Methods

key :: HC a -> Key (HC a) Source #

tryAddFinalizer :: HC a -> Finalizer -> IO () Source #

type Key (HC a) Source # 
type Key (HC a) = Tag a
type CanFinalize (HC a) Source # 
type CanFinalize (HC a) = True

getVal :: HC a -> a Source #

Retrieves the underlying value.

getTag :: HC a -> Tag a Source #

Retrieves the unique tag for the value.

data Tag a Source #

A tag for a value. Tags are unique among values which are simultaneously alive. They also don't keep the corresponding value alive on their own.

Instances

Eq (Tag a) Source # 

Methods

(==) :: Tag a -> Tag a -> Bool #

(/=) :: Tag a -> Tag a -> Bool #

Hashable (Tag a) Source # 

Methods

hashWithSalt :: Int -> Tag a -> Int #

hash :: Tag a -> Int #

class Hashable a where #

Methods

hashWithSalt :: Int -> a -> Int #

hash :: a -> Int #

Instances

Hashable Bool 

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Hashable Char 

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Hashable Double 

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Hashable Float 

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Hashable Int 

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Hashable Int8 

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Hashable Int16 

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Hashable Int32 

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Hashable Int64 

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Hashable Integer 

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

Hashable Natural 

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Hashable Ordering 

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Hashable Word 

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Hashable SomeTypeRep 
Hashable () 

Methods

hashWithSalt :: Int -> () -> Int #

hash :: () -> Int #

Hashable BigNat 

Methods

hashWithSalt :: Int -> BigNat -> Int #

hash :: BigNat -> Int #

Hashable Void 

Methods

hashWithSalt :: Int -> Void -> Int #

hash :: Void -> Int #

Hashable Unique 

Methods

hashWithSalt :: Int -> Unique -> Int #

hash :: Unique -> Int #

Hashable Version 

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Hashable ThreadId 

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

Hashable WordPtr 

Methods

hashWithSalt :: Int -> WordPtr -> Int #

hash :: WordPtr -> Int #

Hashable IntPtr 

Methods

hashWithSalt :: Int -> IntPtr -> Int #

hash :: IntPtr -> Int #

Hashable ShortByteString 
Hashable ByteString 
Hashable ByteString 
Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable a => Hashable [a] 

Methods

hashWithSalt :: Int -> [a] -> Int #

hash :: [a] -> Int #

Hashable a => Hashable (Maybe a) 

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Hashable a => Hashable (Ratio a) 

Methods

hashWithSalt :: Int -> Ratio a -> Int #

hash :: Ratio a -> Int #

Hashable (Ptr a) 

Methods

hashWithSalt :: Int -> Ptr a -> Int #

hash :: Ptr a -> Int #

Hashable (FunPtr a) 

Methods

hashWithSalt :: Int -> FunPtr a -> Int #

hash :: FunPtr a -> Int #

Hashable a => Hashable (Complex a) 

Methods

hashWithSalt :: Int -> Complex a -> Int #

hash :: Complex a -> Int #

Hashable (Fixed a) 

Methods

hashWithSalt :: Int -> Fixed a -> Int #

hash :: Fixed a -> Int #

Hashable a => Hashable (Min a) 

Methods

hashWithSalt :: Int -> Min a -> Int #

hash :: Min a -> Int #

Hashable a => Hashable (Max a) 

Methods

hashWithSalt :: Int -> Max a -> Int #

hash :: Max a -> Int #

Hashable a => Hashable (First a) 

Methods

hashWithSalt :: Int -> First a -> Int #

hash :: First a -> Int #

Hashable a => Hashable (Last a) 

Methods

hashWithSalt :: Int -> Last a -> Int #

hash :: Last a -> Int #

Hashable a => Hashable (WrappedMonoid a) 
Hashable a => Hashable (Option a) 

Methods

hashWithSalt :: Int -> Option a -> Int #

hash :: Option a -> Int #

Hashable a => Hashable (NonEmpty a) 

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Hashable (StableName a) 

Methods

hashWithSalt :: Int -> StableName a -> Int #

hash :: StableName a -> Int #

Hashable a => Hashable (Identity a) 

Methods

hashWithSalt :: Int -> Identity a -> Int #

hash :: Identity a -> Int #

Hashable (Hashed a) 

Methods

hashWithSalt :: Int -> Hashed a -> Int #

hash :: Hashed a -> Int #

Hashable (HC a) #

\(\mathcal{O}(1)\) using the tag

Methods

hashWithSalt :: Int -> HC a -> Int #

hash :: HC a -> Int #

Hashable (Tag a) # 

Methods

hashWithSalt :: Int -> Tag a -> Int #

hash :: Tag a -> Int #

(Hashable a, Hashable b) => Hashable (Either a b) 

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

Hashable (TypeRep k a) 

Methods

hashWithSalt :: Int -> TypeRep k a -> Int #

hash :: TypeRep k a -> Int #

(Hashable a1, Hashable a2) => Hashable (a1, a2) 

Methods

hashWithSalt :: Int -> (a1, a2) -> Int #

hash :: (a1, a2) -> Int #

(Hashable a, Hashable b) => Hashable (Arg a b) 

Methods

hashWithSalt :: Int -> Arg a b -> Int #

hash :: Arg a b -> Int #

Hashable (Proxy k a) 

Methods

hashWithSalt :: Int -> Proxy k a -> Int #

hash :: Proxy k a -> Int #

(Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) 

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int #

hash :: (a1, a2, a3) -> Int #

Hashable a => Hashable (Const k a b) 

Methods

hashWithSalt :: Int -> Const k a b -> Int #

hash :: Const k a b -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int #

hash :: (a1, a2, a3, a4) -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Product * f g a) 

Methods

hashWithSalt :: Int -> Product * f g a -> Int #

hash :: Product * f g a -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Sum * f g a) 

Methods

hashWithSalt :: Int -> Sum * f g a -> Int #

hash :: Sum * f g a -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int #

hash :: (a1, a2, a3, a4, a5) -> Int #

(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Compose * * f g a) 

Methods

hashWithSalt :: Int -> Compose * * f g a -> Int #

hash :: Compose * * f g a -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int #

hash :: (a1, a2, a3, a4, a5, a6) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int #