finitary-derive-2.1.0.0: Flexible and easy deriving of type classes for finitary types.
Copyright(C) Koz Ross 2019
LicenseGPL version 3.0 or later
Maintainerkoz.ross@retro-freedom.nz
StabilityExperimental
PortabilityGHC only
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Finitary.PackBits.Unsafe

Description

From the Kraft-McMillan inequality and the fact that we are not able to have 'fractional' bits, we can derive a fixed-length code into a bitstring for any Finitary type a, with code length \(\lceil \log_{2}(\texttt{Cardinality a}) \rceil\) bits. This code is essentially a binary representation of the index of each inhabitant of a. On that basis, we can derive an Unbox instance, representing the entire Vector as an unboxed bit array.

This encoding is advantageous from the point of view of space - there is no tighter possible packing that preserves \(\Theta(1)\) random access and also allows the full range of Vector operations. If you are concerned about space usage above all, this is the best choice for you.

Because access to individual bits is slower than whole bytes or words, this encoding adds some overhead. Additionally, a primary advantage of bit arrays (the ability to perform 'bulk' operations on bits efficiently) is not made use of here. Therefore, if speed matters more than compactness, this encoding is suboptimal.

This encoding is not thread-safe, in exchange for performance. If you suspect race conditions are possible, it's better to use Data.Finitary.PackBits instead.

Synopsis

Documentation

data PackBits (a :: Type) Source #

An opaque wrapper around a, representing each value as a 'bit-packed' encoding.

Instances

Instances details
(Finitary a, 1 <= Cardinality a) => Vector Vector (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

(Finitary a, 1 <= Cardinality a) => MVector MVector (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

(Finitary a, 1 <= Cardinality a) => Bounded (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Eq (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

(==) :: PackBits a -> PackBits a -> Bool #

(/=) :: PackBits a -> PackBits a -> Bool #

Ord (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

compare :: PackBits a -> PackBits a -> Ordering #

(<) :: PackBits a -> PackBits a -> Bool #

(<=) :: PackBits a -> PackBits a -> Bool #

(>) :: PackBits a -> PackBits a -> Bool #

(>=) :: PackBits a -> PackBits a -> Bool #

max :: PackBits a -> PackBits a -> PackBits a #

min :: PackBits a -> PackBits a -> PackBits a #

Show (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

showsPrec :: Int -> PackBits a -> ShowS #

show :: PackBits a -> String #

showList :: [PackBits a] -> ShowS #

Binary (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

put :: PackBits a -> Put #

get :: Get (PackBits a) #

putList :: [PackBits a] -> Put #

NFData (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

rnf :: PackBits a -> () #

(Finitary a, 1 <= Cardinality a) => Finitary (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Associated Types

type Cardinality (PackBits a) :: Nat #

Hashable (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

hashWithSalt :: Int -> PackBits a -> Int #

hash :: PackBits a -> Int #

(Finitary a, 1 <= Cardinality a) => Unbox (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

newtype MVector s (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

newtype MVector s (PackBits a) = MV_PackBits (MVector s Bit)
newtype Vector (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

type Cardinality (PackBits a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

pattern Packed :: forall (a :: Type). (Finitary a, 1 <= Cardinality a) => a -> PackBits a Source #

To provide (something that resembles a) data constructor for PackBits, we provide the following pattern. It can be used like any other data constructor:

import Data.Finitary.PackBits

anInt :: PackBits Int
anInt = Packed 10

isPackedEven :: PackBits Int -> Bool
isPackedEven (Packed x) = even x

Every pattern match, and data constructor call, performs a \(\Theta(\log_{2}(\texttt{Cardinality a}))\) encoding or decoding operation. Use with this in mind.

data BulkPack a Source #

This wrapper provides an efficient Hashable instance (hash the entire underlying bit-packed vector, rather than each element individually), as well as a Binary instance (which stores or reads the entire blob of bits 'in one go').

Instances

Instances details
(Finitary a, 1 <= Cardinality a) => Eq (BulkPack a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

(==) :: BulkPack a -> BulkPack a -> Bool #

(/=) :: BulkPack a -> BulkPack a -> Bool #

(Finitary a, 1 <= Cardinality a) => Ord (BulkPack a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

compare :: BulkPack a -> BulkPack a -> Ordering #

(<) :: BulkPack a -> BulkPack a -> Bool #

(<=) :: BulkPack a -> BulkPack a -> Bool #

(>) :: BulkPack a -> BulkPack a -> Bool #

(>=) :: BulkPack a -> BulkPack a -> Bool #

max :: BulkPack a -> BulkPack a -> BulkPack a #

min :: BulkPack a -> BulkPack a -> BulkPack a #

Binary (BulkPack a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

put :: BulkPack a -> Put #

get :: Get (BulkPack a) #

putList :: [BulkPack a] -> Put #

NFData (BulkPack a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

rnf :: BulkPack a -> () #

Hashable (BulkPack a) Source # 
Instance details

Defined in Data.Finitary.PackBits.Unsafe

Methods

hashWithSalt :: Int -> BulkPack a -> Int #

hash :: BulkPack a -> Int #