Safe Haskell | None |
---|---|
Language | Haskell98 |
- myToStrict :: ByteString -> ByteString
- type MFun = Char
- type VarName = String
- data ShowF
- = Expr ByteString
- | Var Int
- type Context = BasicHashTable Int (StableName MFun, MFun, [ShowF], Int)
- data Error = Error String
- data StatW = StatW (Context, [ShowF], ByteString)
- data STW a = STW (StatW -> (StatW, a))
- empty :: HashTable h => IO (h RealWorld k v)
- assocs :: (Hashable a, HashTable h, Ord a) => h RealWorld a b -> [(a, b)]
- insert :: (Hashable k, Eq k, HashTable h) => k -> v -> h RealWorld k v -> h RealWorld k v
- delete :: (Hashable k, Eq k, HashTable h) => k -> h RealWorld k v -> h RealWorld k v
- lookup :: (Hashable k, Eq k, HashTable h) => k -> h RealWorld k v -> Maybe v
- toList :: (Hashable k, Eq k, HashTable h) => h RealWorld k v -> [(k, v)]
- fromList :: (Hashable k, Eq k, HashTable h) => [(k, v)] -> h RealWorld k v
- addrHash :: Context -> a -> IO (Either Int Int)
- readContext :: ByteString -> ByteString -> (ByteString, ByteString)
- hasht :: a -> (Int, t)
- varName :: t -> [Char]
- numVar :: String -> Maybe Int
Documentation
myToStrict :: ByteString -> ByteString Source #
type Context = BasicHashTable Int (StableName MFun, MFun, [ShowF], Int) Source #
addrHash :: Context -> a -> IO (Either Int Int) Source #
return a unique hash identifier for an object
the context assures that no StableName used in addrStr is garbage collected,
so the hashes are constant and the correspondence address - string
remain one to one as long as the context is not garbage collected.
Left is returned if it is the first time that addHash
is called for that variable
readContext :: ByteString -> ByteString -> (ByteString, ByteString) Source #
varName :: t -> [Char] Source #
two variables that point to the same address will have identical varname (derived from import System.Mem.StableName)varName:: a -> String . The stable names of during the serializing deserializing process are not deleted . This is assured by the pointers in the context, so the hash values remain and the comparison of varNames is correct.