Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Bin a
- class Binary a where
- data BinHandle
- type SymbolTable = Array Int Name
- type Dictionary = Array Int FastString
- openBinMem :: Int -> IO BinHandle
- seekBin :: BinHandle -> Bin a -> IO ()
- seekBy :: BinHandle -> Int -> IO ()
- tellBin :: BinHandle -> IO (Bin a)
- castBin :: Bin a -> Bin b
- isEOFBin :: BinHandle -> IO Bool
- withBinBuffer :: BinHandle -> (ByteString -> IO a) -> IO a
- writeBinMem :: BinHandle -> FilePath -> IO ()
- readBinMem :: FilePath -> IO BinHandle
- putAt :: Binary a => BinHandle -> Bin a -> a -> IO ()
- getAt :: Binary a => BinHandle -> Bin a -> IO a
- putByte :: BinHandle -> Word8 -> IO ()
- getByte :: BinHandle -> IO Word8
- lazyGet :: Binary a => BinHandle -> IO a
- lazyPut :: Binary a => BinHandle -> a -> IO ()
- data UserData = UserData {
- ud_get_name :: BinHandle -> IO Name
- ud_get_fs :: BinHandle -> IO FastString
- ud_put_nonbinding_name :: BinHandle -> Name -> IO ()
- ud_put_binding_name :: BinHandle -> Name -> IO ()
- ud_put_fs :: BinHandle -> FastString -> IO ()
- getUserData :: BinHandle -> UserData
- setUserData :: BinHandle -> UserData -> BinHandle
- newReadState :: (BinHandle -> IO Name) -> (BinHandle -> IO FastString) -> UserData
- newWriteState :: (BinHandle -> Name -> IO ()) -> (BinHandle -> Name -> IO ()) -> (BinHandle -> FastString -> IO ()) -> UserData
- putDictionary :: BinHandle -> Int -> UniqFM (Int, FastString) -> IO ()
- getDictionary :: BinHandle -> IO Dictionary
- putFS :: BinHandle -> FastString -> IO ()
Documentation
type Dictionary = Array Int FastString Source #
withBinBuffer :: BinHandle -> (ByteString -> IO a) -> IO a Source #
Get access to the underlying buffer.
It is quite important that no references to the ByteString
leak out of the
continuation lest terrible things happen.
For writing instances
Lazy Binary I/O
User data
Information we keep around during interface file
serialization/deserialization. Namely we keep the functions for serializing
and deserializing Name
s and FastString
s. We do this because we actually
use serialization in two distinct settings,
- When serializing interface files themselves
- When computing the fingerprint of an IfaceDecl (which we computing by hashing its Binary serialization)
These two settings have different needs while serializing Names:
- Names in interface files are serialized via a symbol table (see Note [Symbol table representation of names] in BinIface).
- During fingerprinting a binding Name is serialized as the OccName and a non-binding Name is serialized as the fingerprint of the thing they represent. See Note [Fingerprinting IfaceDecls] for further discussion.
UserData | |
|
getUserData :: BinHandle -> UserData Source #
putDictionary :: BinHandle -> Int -> UniqFM (Int, FastString) -> IO () Source #
getDictionary :: BinHandle -> IO Dictionary Source #