compact-word-vectors-0.1: Small vectors of small integers stored very compactly.

Safe HaskellNone
LanguageHaskell2010

Data.Vector.Compact.Blob

Contents

Description

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

the Blob type

data Blob Source #

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.

Instances
Eq Blob Source # 
Instance details

Defined in Data.Vector.Compact.Blob

Methods

(==) :: Blob -> Blob -> Bool #

(/=) :: Blob -> Blob -> Bool #

Show Blob Source # 
Instance details

Defined in Data.Vector.Compact.Blob

Methods

showsPrec :: Int -> Blob -> ShowS #

show :: Blob -> String #

showList :: [Blob] -> ShowS #

Bits Blob Source # 
Instance details

Defined in Data.Vector.Compact.Blob

FiniteBits Blob Source # 
Instance details

Defined in Data.Vector.Compact.Blob

Conversion to/from lists

Conversion to/from ByteArray-s

blobFromByteArray :: ByteArray -> Blob Source #

Note: we pad the input with zero bytes, assuming little-endian architecture.

Hexadecimal

newtype Hex Source #

Constructors

Hex Word64 
Instances
Show Hex Source # 
Instance details

Defined in Data.Vector.Compact.Blob

Methods

showsPrec :: Int -> Hex -> ShowS #

show :: Hex -> String #

showList :: [Hex] -> ShowS #

Peek

peekByte :: 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.

extractSmallWord64_naive :: Int -> Blob -> Int -> Word64 Source #

An alternate implementation using testBit, for testing purposes only

change size

map and zipWith