Safe Haskell | None |
---|---|
Language | Haskell2010 |
Blobs are raw data in continuous regions of memory.
This library provides a type for blobs consisting 64 bit words which is optimized for small sizes. They take:
- only 1 extra word up for blobs of size up to 48 bytes (that is, up to 6
Word64
-s); - but (unfortunataly) 4 extra words above that.
(This particular tradeoff was chosen so that pointer tagging still works on 64 bit architectures: there are 7 constructors of the data type.)
The Blob
data type is useful if you want to store large amounts of small,
serialized data. Some example use cases:
- small vectors of small nonnegative integers (for example: partitions, permutations, monomials)
- cryptographic hashes
- tables indexed by such things
Synopsis
- data Blob
- blobTag :: Blob -> Int
- blobSizeInWords :: Blob -> Int
- blobSizeInBytes :: Blob -> Int
- blobSizeInBits :: Blob -> Int
- blobFromWordList :: [Word64] -> Blob
- blobFromWordListN :: Int -> [Word64] -> Blob
- blobToWordList :: Blob -> [Word64]
- blobFromByteArray :: ByteArray -> Blob
- blobToByteArray :: Blob -> ByteArray
- eqBlob :: Blob -> Blob -> Bool
- head :: Blob -> Word64
- tail :: Blob -> Blob
- last :: Blob -> Word64
- consWord :: Word64 -> Blob -> Blob
- snocWord :: Blob -> Word64 -> Blob
- indexWord :: Blob -> Int -> Word64
- indexByte :: Blob -> Int -> Word8
- extractSmallWord :: Integral a => Int -> Blob -> Int -> a
- extractSmallWord64 :: Int -> Blob -> Int -> Word64
- extendToSize :: Int -> Blob -> Blob
- cutToSize :: Int -> Blob -> Blob
- forceToSize :: Int -> Blob -> Blob
- mapBlob :: (Word64 -> Word64) -> Blob -> Blob
- shortZipWith :: (Word64 -> Word64 -> Word64) -> Blob -> Blob -> Blob
- longZipWith :: (Word64 -> Word64 -> Word64) -> Blob -> Blob -> Blob
- unsafeZipWith :: (Word64 -> Word64 -> Word64) -> Blob -> Blob -> Blob
- newtype Hex = Hex Word64
- hexWord64 :: Word64 -> String
- hexWord64_ :: Word64 -> String
- peekBlob :: Int -> Ptr Word64 -> IO Blob
- pokeBlob :: Ptr Word64 -> Blob -> IO Int
- type CFun10 a = CInt -> Ptr Word64 -> IO a
- type CFun20 a = CInt -> Ptr Word64 -> CInt -> Ptr Word64 -> IO a
- type CFun11 a = CInt -> Ptr Word64 -> Ptr CInt -> Ptr Word64 -> IO a
- type CFun21 a = CInt -> Ptr Word64 -> CInt -> Ptr Word64 -> Ptr CInt -> Ptr Word64 -> IO a
- type CFun11_ = CFun11 ()
- type CFun21_ = CFun21 ()
- wrapCFun10 :: CFun10 a -> Blob -> a
- wrapCFun20 :: CFun20 a -> Blob -> Blob -> a
- wrapCFun11 :: CFun11 a -> (Int -> Int) -> Blob -> (a, Blob)
- wrapCFun21 :: CFun21 a -> (Int -> Int -> Int) -> Blob -> Blob -> (a, Blob)
- wrapCFun11_ :: CFun11_ -> (Int -> Int) -> Blob -> Blob
- wrapCFun21_ :: CFun21_ -> (Int -> Int -> Int) -> Blob -> Blob -> Blob
The Blob type
A Blob
is a nonempty array of Word64
-s.
For arrays of length at most 6 (that is, at most 48 bytes), there is only a single
machine word overhead in memory consumption. For larger arrays, there is 4 words of overhead.
Blob1 !Word64 | |
Blob2 !Word64 !Word64 | |
Blob3 !Word64 !Word64 !Word64 | |
Blob4 !Word64 !Word64 !Word64 !Word64 | |
Blob5 !Word64 !Word64 !Word64 !Word64 !Word64 | |
Blob6 !Word64 !Word64 !Word64 !Word64 !Word64 !Word64 | |
BlobN !ByteArray |
Instances
Eq Blob Source # | |
Show Blob Source # | |
Bits Blob Source # | Implementation note: When necessary, the bitwise operations consider the blobs
extended to infinity with zero withs. This is especially important with |
Defined in Data.Vector.Compact.Blob (.&.) :: Blob -> Blob -> Blob # (.|.) :: Blob -> Blob -> Blob # complement :: Blob -> Blob # shift :: Blob -> Int -> Blob # rotate :: Blob -> Int -> Blob # setBit :: Blob -> Int -> Blob # clearBit :: Blob -> Int -> Blob # complementBit :: Blob -> Int -> Blob # testBit :: Blob -> Int -> Bool # bitSizeMaybe :: Blob -> Maybe Int # shiftL :: Blob -> Int -> Blob # unsafeShiftL :: Blob -> Int -> Blob # shiftR :: Blob -> Int -> Blob # unsafeShiftR :: Blob -> Int -> Blob # rotateL :: Blob -> Int -> Blob # | |
FiniteBits Blob Source # | |
Defined in Data.Vector.Compact.Blob |
blobSizeInBytes :: Blob -> Int Source #
blobSizeInBits :: Blob -> Int Source #
Conversion to/from lists
blobFromWordList :: [Word64] -> Blob Source #
blobToWordList :: Blob -> [Word64] Source #
Conversion to/from ByteArray
-s
blobFromByteArray :: ByteArray -> Blob Source #
Note: we pad the input with zero bytes, assuming little-endian architecture.
blobToByteArray :: Blob -> ByteArray Source #
Equality comparison
Head, tail, cons, etc
Indexing
indexByte :: Blob -> Int -> Word8 Source #
NOTE: We assume a little-endian architecture here. Though it seems that since GHC does not gives us direct access to the closure, it doesn't matter after all...
extractSmallWord :: Integral a => Int -> Blob -> Int -> a Source #
extractSmallWord n blob ofs
extracts a small word of n
bits starting from the
ofs
-th bit. This should satisfy
testBit (extractSmallWord n blob ofs) i == testBit blob (ofs+i)
NOTE: we assume that n
is at most the bits in Word
, and that ofs+n
is less
than the size (in bits) of the blob.
Resizing
Higher-order functions
longZipWith :: (Word64 -> Word64 -> Word64) -> Blob -> Blob -> Blob Source #
Extend the shorter blob with zeros
unsafeZipWith :: (Word64 -> Word64 -> Word64) -> Blob -> Blob -> Blob Source #
We assume that the two blobs has the same size!
Hexadecimal printing
hexWord64_ :: Word64 -> String Source #
(Indirect) access to the raw data
Note: Because GHC does not support direct manipulation of heap data (the garbage collector can move it anytime), these involve copying.
Wrappers for C implementations
As above, these involve copying of the data (both inputs and outputs);
so they first allocate temporary buffers, copy the data into them
call the C function, and copy the result to a new Blob
.
Naming conventions: For example CFun21
means 2 Blob inputs and 1 Blob output.
wrapCFun10 :: CFun10 a -> Blob -> a Source #