Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data Bin (a :: k)
- data RelBin (a :: k) = RelBin {
- relBin_anchor :: !(Bin a)
- relBin_offset :: !(RelBinPtr a)
- getRelBin :: forall {k} (a :: k). ReadBinHandle -> IO (RelBin a)
- class Binary a where
- put_ :: WriteBinHandle -> a -> IO ()
- put :: WriteBinHandle -> a -> IO (Bin a)
- get :: ReadBinHandle -> IO a
- data ReadBinHandle
- data WriteBinHandle
- type SymbolTable a = Array Int a
- type Dictionary = SymbolTable FastString
- data BinData = BinData Int BinArray
- dataHandle :: BinData -> IO ReadBinHandle
- handleData :: WriteBinHandle -> IO BinData
- unsafeUnpackBinBuffer :: ByteString -> IO ReadBinHandle
- openBinMem :: Int -> IO WriteBinHandle
- seekBinWriter :: forall {k} (a :: k). WriteBinHandle -> Bin a -> IO ()
- seekBinReader :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO ()
- seekBinReaderRel :: forall {k} (a :: k). ReadBinHandle -> RelBin a -> IO ()
- tellBinReader :: forall {k} (a :: k). ReadBinHandle -> IO (Bin a)
- tellBinWriter :: forall {k} (a :: k). WriteBinHandle -> IO (Bin a)
- castBin :: forall {k1} {k2} (a :: k1) (b :: k2). Bin a -> Bin b
- withBinBuffer :: WriteBinHandle -> (ByteString -> IO a) -> IO a
- freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle
- shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle
- thawReadHandle :: ReadBinHandle -> IO WriteBinHandle
- foldGet :: Binary a => Word -> ReadBinHandle -> b -> (Word -> a -> b -> IO b) -> IO b
- foldGet' :: Binary a => Word -> ReadBinHandle -> b -> (Word -> a -> b -> IO b) -> IO b
- writeBinMem :: WriteBinHandle -> FilePath -> IO ()
- readBinMem :: FilePath -> IO ReadBinHandle
- readBinMemN :: Int -> FilePath -> IO (Maybe ReadBinHandle)
- putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO ()
- getAt :: Binary a => ReadBinHandle -> Bin a -> IO a
- putAtRel :: forall {k} (a :: k). WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO ()
- forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b)
- forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO ()
- forwardGet :: ReadBinHandle -> IO a -> IO a
- forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b)
- forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO ()
- forwardGetRel :: ReadBinHandle -> IO a -> IO a
- putByte :: WriteBinHandle -> Word8 -> IO ()
- getByte :: ReadBinHandle -> IO Word8
- putByteString :: WriteBinHandle -> ByteString -> IO ()
- getByteString :: ReadBinHandle -> Int -> IO ByteString
- putULEB128 :: (Integral a, FiniteBits a) => WriteBinHandle -> a -> IO ()
- getULEB128 :: (Integral a, FiniteBits a) => ReadBinHandle -> IO a
- putSLEB128 :: (Integral a, Bits a) => WriteBinHandle -> a -> IO ()
- getSLEB128 :: (Show a, Integral a, FiniteBits a) => ReadBinHandle -> IO a
- newtype FixedLengthEncoding a = FixedLengthEncoding {
- unFixedLength :: a
- lazyGet :: Binary a => ReadBinHandle -> IO a
- lazyPut :: Binary a => WriteBinHandle -> a -> IO ()
- lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a
- lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO ()
- lazyGetMaybe :: Binary a => ReadBinHandle -> IO (Maybe a)
- lazyPutMaybe :: Binary a => WriteBinHandle -> Maybe a -> IO ()
- data ReaderUserData
- getReaderUserData :: ReadBinHandle -> ReaderUserData
- setReaderUserData :: ReadBinHandle -> ReaderUserData -> ReadBinHandle
- noReaderUserData :: ReaderUserData
- data WriterUserData
- getWriterUserData :: WriteBinHandle -> WriterUserData
- setWriterUserData :: WriteBinHandle -> WriterUserData -> WriteBinHandle
- noWriterUserData :: WriterUserData
- mkWriterUserData :: [SomeBinaryWriter] -> WriterUserData
- mkReaderUserData :: [SomeBinaryReader] -> ReaderUserData
- newReadState :: (ReadBinHandle -> IO Name) -> (ReadBinHandle -> IO FastString) -> ReaderUserData
- newWriteState :: (WriteBinHandle -> Name -> IO ()) -> (WriteBinHandle -> Name -> IO ()) -> (WriteBinHandle -> FastString -> IO ()) -> WriterUserData
- addReaderToUserData :: Typeable a => BinaryReader a -> ReadBinHandle -> ReadBinHandle
- addWriterToUserData :: Typeable a => BinaryWriter a -> WriteBinHandle -> WriteBinHandle
- findUserDataReader :: Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a
- findUserDataWriter :: Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a
- newtype BinaryReader s = BinaryReader {
- getEntry :: ReadBinHandle -> IO s
- newtype BinaryWriter s = BinaryWriter {
- putEntry :: WriteBinHandle -> s -> IO ()
- mkWriter :: (WriteBinHandle -> s -> IO ()) -> BinaryWriter s
- mkReader :: (ReadBinHandle -> IO s) -> BinaryReader s
- data SomeBinaryReader
- data SomeBinaryWriter
- mkSomeBinaryReader :: Typeable a => BinaryReader a -> SomeBinaryReader
- mkSomeBinaryWriter :: Typeable a => BinaryWriter a -> SomeBinaryWriter
- data ReaderTable a = ReaderTable {
- getTable :: ReadBinHandle -> IO (SymbolTable a)
- mkReaderFromTable :: SymbolTable a -> BinaryReader a
- newtype WriterTable = WriterTable {
- putTable :: WriteBinHandle -> IO Int
- initFastStringReaderTable :: IO (ReaderTable FastString)
- initFastStringWriterTable :: IO (WriterTable, BinaryWriter FastString)
- putDictionary :: WriteBinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO ()
- getDictionary :: ReadBinHandle -> IO Dictionary
- putFS :: WriteBinHandle -> FastString -> IO ()
- data FSTable = FSTable {
- fs_tab_next :: !FastMutInt
- fs_tab_map :: !(IORef (UniqFM FastString (Int, FastString)))
- getDictFastString :: Dictionary -> ReadBinHandle -> IO FastString
- putDictFastString :: FSTable -> WriteBinHandle -> FastString -> IO ()
- data GenericSymbolTable (m :: Type -> Type) = GenericSymbolTable {
- gen_symtab_next :: !FastMutInt
- gen_symtab_map :: !(IORef (m Int))
- gen_symtab_to_write :: !(IORef [Key m])
- initGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => IO (GenericSymbolTable m)
- getGenericSymtab :: Binary a => SymbolTable a -> ReadBinHandle -> IO a
- putGenericSymTab :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> WriteBinHandle -> Key m -> IO ()
- getGenericSymbolTable :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a)
- putGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> (WriteBinHandle -> Key m -> IO ()) -> WriteBinHandle -> IO Int
- newtype BinSpan = BinSpan {}
- newtype BinSrcSpan = BinSrcSpan {}
- newtype BinLocated a = BinLocated {
- unBinLocated :: Located a
- newtype BindingName = BindingName {}
- simpleBindingNameWriter :: BinaryWriter Name -> BinaryWriter BindingName
- simpleBindingNameReader :: BinaryReader Name -> BinaryReader BindingName
- data FullBinData = FullBinData {
- fbd_readerUserData :: ReaderUserData
- fbd_off_s :: !Int
- fbd_off_e :: !Int
- fbd_size :: !Int
- fbd_buffer :: !BinArray
- freezeBinHandle :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO FullBinData
- thawBinHandle :: FullBinData -> IO ReadBinHandle
- putFullBinData :: WriteBinHandle -> FullBinData -> IO ()
- type BinArray = ForeignPtr Word8
Documentation
Like a Bin
but is used to store relative offset pointers.
Relative offset pointers store a relative location, but also contain an
anchor that allow to obtain the absolute offset.
RelBin | |
|
Do not rely on instance sizes for general types, we use variable length encoding for many of them.
put_ :: WriteBinHandle -> a -> IO () Source #
put :: WriteBinHandle -> a -> IO (Bin a) Source #
get :: ReadBinHandle -> IO a Source #
Instances
data ReadBinHandle Source #
A read-only handle that can be used to deserialise binary data from a buffer.
The buffer is an unboxed binary array.
data WriteBinHandle Source #
A write-only handle that can be used to serialise binary data into a buffer.
The buffer is an unboxed binary array.
type SymbolTable a = Array Int a Source #
Symbols that are read from disk.
The SymbolTable
index starts on '0'.
type Dictionary = SymbolTable FastString Source #
A SymbolTable
of FastString
s.
dataHandle :: BinData -> IO ReadBinHandle Source #
handleData :: WriteBinHandle -> IO BinData Source #
openBinMem :: Int -> IO WriteBinHandle Source #
seekBinWriter :: forall {k} (a :: k). WriteBinHandle -> Bin a -> IO () Source #
seekBinReader :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO () Source #
SeekBin but without calling expandBin
seekBinReaderRel :: forall {k} (a :: k). ReadBinHandle -> RelBin a -> IO () Source #
tellBinReader :: forall {k} (a :: k). ReadBinHandle -> IO (Bin a) Source #
tellBinWriter :: forall {k} (a :: k). WriteBinHandle -> IO (Bin a) Source #
withBinBuffer :: WriteBinHandle -> (ByteString -> IO a) -> IO a Source #
Get access to the underlying buffer.
freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle Source #
Freeze the given WriteBinHandle
and turn it into an equivalent ReadBinHandle
.
The current offset of the WriteBinHandle
is maintained in the new ReadBinHandle
.
shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle Source #
Copy the BinBuffer to a new BinBuffer which is exactly the right size. This performs a copy of the underlying buffer. The buffer may be truncated if the offset is not at the end of the written output.
UserData is also discarded during the copy You should just use this when translating a Put handle into a Get handle.
writeBinMem :: WriteBinHandle -> FilePath -> IO () Source #
readBinMem :: FilePath -> IO ReadBinHandle Source #
readBinMemN :: Int -> FilePath -> IO (Maybe ReadBinHandle) Source #
forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b) Source #
outputs A after B but allows A to be read before B
by using a forward reference.forwardPut
put_A put_B
forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () Source #
forwardGet :: ReadBinHandle -> IO a -> IO a Source #
Read a value stored using a forward reference
The forward reference is expected to be an absolute offset.
forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b) Source #
outputs A after B but allows A to be read before B
by using a forward reference.forwardPutRel
put_A put_B
This forward reference is a relative offset that allows us to skip over the
result of put_A
.
forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () Source #
Like forwardGetRel
, but discard the result.
forwardGetRel :: ReadBinHandle -> IO a -> IO a Source #
Read a value stored using a forward reference.
The forward reference is expected to be a relative offset.
For writing instances
putByteString :: WriteBinHandle -> ByteString -> IO () Source #
Put a ByteString without its length (can't be read back without knowing the length!)
getByteString :: ReadBinHandle -> Int -> IO ByteString Source #
Get a ByteString whose length is known
Variable length encodings
putULEB128 :: (Integral a, FiniteBits a) => WriteBinHandle -> a -> IO () Source #
getULEB128 :: (Integral a, FiniteBits a) => ReadBinHandle -> IO a Source #
putSLEB128 :: (Integral a, Bits a) => WriteBinHandle -> a -> IO () Source #
getSLEB128 :: (Show a, Integral a, FiniteBits a) => ReadBinHandle -> IO a Source #
Fixed length encoding
newtype FixedLengthEncoding a Source #
Encode the argument in its full length. This is different from many default binary instances which make no guarantee about the actual encoding and might do things using variable length encoding.
Instances
Lazy Binary I/O
lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a Source #
lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () Source #
lazyGetMaybe :: Binary a => ReadBinHandle -> IO (Maybe a) Source #
Deserialize a value serialized by lazyPutMaybe
.
lazyPutMaybe :: Binary a => WriteBinHandle -> Maybe a -> IO () Source #
Serialize the constructor strictly but lazily serialize a value inside a
Just
.
This way we can check for the presence of a value without deserializing the value itself.
User data
data ReaderUserData Source #
UserData required to deserialise symbols for interface files.
See Note [Binary UserData]
data WriterUserData Source #
UserData required to serialise symbols for interface files.
See Note [Binary UserData]
:: (ReadBinHandle -> IO Name) | how to deserialize |
-> (ReadBinHandle -> IO FastString) | |
-> ReaderUserData |
:: (WriteBinHandle -> Name -> IO ()) | how to serialize non-binding |
-> (WriteBinHandle -> Name -> IO ()) | how to serialize binding |
-> (WriteBinHandle -> FastString -> IO ()) | |
-> WriterUserData |
addReaderToUserData :: Typeable a => BinaryReader a -> ReadBinHandle -> ReadBinHandle Source #
Add SomeBinaryReader
as a known binary decoder.
If a BinaryReader
for the associated type already exists in ReaderUserData
,
it is overwritten.
addWriterToUserData :: Typeable a => BinaryWriter a -> WriteBinHandle -> WriteBinHandle Source #
Add SomeBinaryWriter
as a known binary encoder.
If a BinaryWriter
for the associated type already exists in WriterUserData
,
it is overwritten.
findUserDataReader :: Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a Source #
Find the BinaryReader
for the Binary
instance for the type identified by 'Proxy a'.
If no BinaryReader
has been configured before, this function will panic.
findUserDataWriter :: Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a Source #
Find the BinaryWriter
for the Binary
instance for the type identified by 'Proxy a'.
If no BinaryWriter
has been configured before, this function will panic.
Binary Readers & Writers
newtype BinaryReader s Source #
BinaryReader | |
|
Instances
Functor BinaryReader Source # | |
Defined in GHC.Utils.Binary fmap :: (a -> b) -> BinaryReader a -> BinaryReader b # (<$) :: a -> BinaryReader b -> BinaryReader a # |
newtype BinaryWriter s Source #
BinaryWriter | |
|
mkWriter :: (WriteBinHandle -> s -> IO ()) -> BinaryWriter s Source #
mkReader :: (ReadBinHandle -> IO s) -> BinaryReader s Source #
data SomeBinaryReader Source #
Existential for BinaryReader
with a type witness.
data SomeBinaryWriter Source #
Existential for BinaryWriter
with a type witness.
mkSomeBinaryReader :: Typeable a => BinaryReader a -> SomeBinaryReader Source #
mkSomeBinaryWriter :: Typeable a => BinaryWriter a -> SomeBinaryWriter Source #
Tables
data ReaderTable a Source #
A ReaderTable
describes how to deserialise a table from disk,
and how to create a BinaryReader
that looks up values in the deduplication table.
ReaderTable | |
|
newtype WriterTable Source #
A WriterTable
is an interface any deduplication table can implement to
describe how the table can be written to disk.
WriterTable | |
|
String table ("dictionary")
putDictionary :: WriteBinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO () Source #
putFS :: WriteBinHandle -> FastString -> IO () Source #
FSTable | |
|
getDictFastString :: Dictionary -> ReadBinHandle -> IO FastString Source #
putDictFastString :: FSTable -> WriteBinHandle -> FastString -> IO () Source #
Generic deduplication table
data GenericSymbolTable (m :: Type -> Type) Source #
The GenericSymbolTable
stores a mapping from already seen elements to an index.
If an element wasn't seen before, it is added to the mapping together with a fresh
index.
GenericSymbolTable
is a variant of a BinSymbolTable
that is polymorphic in the table implementation.
As such it can be used with any container that implements the TrieMap
type class.
While GenericSymbolTable
is similar to the BinSymbolTable
, it supports storing tree-like
structures such as Type
and IfaceType
more efficiently.
GenericSymbolTable | |
|
initGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => IO (GenericSymbolTable m) Source #
Initialise a GenericSymbolTable
, initialising the index to '0'.
getGenericSymtab :: Binary a => SymbolTable a -> ReadBinHandle -> IO a Source #
Read a value from a SymbolTable
.
putGenericSymTab :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> WriteBinHandle -> Key m -> IO () Source #
Write an element 'Key m' to the given WriteBinHandle
.
If the element was seen before, we simply write the index of that element to the
WriteBinHandle
. If we haven't seen it before, we add the element to
the GenericSymbolTable
, increment the index, and return this new index.
getGenericSymbolTable :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) Source #
Read the elements of a GenericSymbolTable
from disk into a SymbolTable
.
putGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> (WriteBinHandle -> Key m -> IO ()) -> WriteBinHandle -> IO Int Source #
Serialise the GenericSymbolTable
to disk.
Since GenericSymbolTable
stores tree-like structures, such as IfaceType
,
serialising an element can add new elements to the mapping.
Thus, putGenericSymbolTable
first serialises all values, and then checks whether any
new elements have been discovered. If so, repeat the loop.
Newtype wrappers
newtype BinSrcSpan Source #
Instances
Binary BinSrcSpan Source # | |
Defined in GHC.Utils.Binary put_ :: WriteBinHandle -> BinSrcSpan -> IO () Source # put :: WriteBinHandle -> BinSrcSpan -> IO (Bin BinSrcSpan) Source # get :: ReadBinHandle -> IO BinSrcSpan Source # |
newtype BinLocated a Source #
Instances
Binary a => Binary (BinLocated a) Source # | |
Defined in GHC.Utils.Binary put_ :: WriteBinHandle -> BinLocated a -> IO () Source # put :: WriteBinHandle -> BinLocated a -> IO (Bin (BinLocated a)) Source # get :: ReadBinHandle -> IO (BinLocated a) Source # |
Newtypes for types that have canonically more than one valid encoding
newtype BindingName Source #
Newtype to serialise binding names differently to non-binding Name
.
See Note [Binary UserData]
Instances
Eq BindingName Source # | |
Defined in GHC.Utils.Binary (==) :: BindingName -> BindingName -> Bool # (/=) :: BindingName -> BindingName -> Bool # |
data FullBinData Source #
FullBinData
stores a slice to a BinArray
.
It requires less memory than ReadBinHandle
, and can be constructed from
a ReadBinHandle
via freezeBinHandle
and turned back into a
ReadBinHandle
using thawBinHandle
.
Additionally, the byte array slice can be put into a WriteBinHandle
without extra
conversions via putFullBinData
.
FullBinData | |
|
Instances
Eq FullBinData Source # | |
Defined in GHC.Utils.Binary (==) :: FullBinData -> FullBinData -> Bool # (/=) :: FullBinData -> FullBinData -> Bool # | |
Ord FullBinData Source # | |
Defined in GHC.Utils.Binary compare :: FullBinData -> FullBinData -> Ordering # (<) :: FullBinData -> FullBinData -> Bool # (<=) :: FullBinData -> FullBinData -> Bool # (>) :: FullBinData -> FullBinData -> Bool # (>=) :: FullBinData -> FullBinData -> Bool # max :: FullBinData -> FullBinData -> FullBinData # min :: FullBinData -> FullBinData -> FullBinData # |
freezeBinHandle :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO FullBinData Source #
Freeze a ReadBinHandle
and a start index into a FullBinData
.
FullBinData
stores a slice starting from the 'Bin a' location to the current
offset of the ReadBinHandle
.
thawBinHandle :: FullBinData -> IO ReadBinHandle Source #
Turn the FullBinData
into a ReadBinHandle
, setting the ReadBinHandle
offset to the start of the FullBinData
and restore the ReaderUserData
that was
obtained from freezeBinHandle
.
putFullBinData :: WriteBinHandle -> FullBinData -> IO () Source #
Write the FullBinData
slice into the WriteBinHandle
.
type BinArray = ForeignPtr Word8 Source #