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

Data.Finitary.PackBytes

Description

If a type a is Finitary, each inhabitant of a has an index, which can be represented as a byte string of a fixed length (as the number of indexes is finite). Essentially, we can represent any value of a as a fixed-length string over an alphabet of cardinality \(256\). Based on this, we can derive a Unbox instance, representing a Vector as a large byte string. This also allows us to provide a Storable instance for a.

This encoding is fairly tight in terms of space use, especially for types whose cardinalities are large. Additionally, byte-access is considerably faster than bit-access on most architectures. If your types have large cardinalities, and minimal space use isn't a concern, this encoding is good.

Some architectures prefer whole-word access - on these, there can be some overheads using this encoding. Additionally, the encoding and decoding step for this encoding is longer than the one for Data.Finitary.PackWords. If Cardinality a < Cardinality Word, you should consider a different encoding - in particular, check Data.Finitary.PackInto, which is more flexible and faster, with greater control over space usage.

Synopsis

Documentation

data PackBytes (a :: Type) Source #

An opaque wrapper around a, representing each value as a byte string.

Instances

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

Defined in Data.Finitary.PackBytes

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

Defined in Data.Finitary.PackBytes

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

Defined in Data.Finitary.PackBytes

Eq (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

(==) :: PackBytes a -> PackBytes a -> Bool

(/=) :: PackBytes a -> PackBytes a -> Bool

Ord (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

compare :: PackBytes a -> PackBytes a -> Ordering

(<) :: PackBytes a -> PackBytes a -> Bool

(<=) :: PackBytes a -> PackBytes a -> Bool

(>) :: PackBytes a -> PackBytes a -> Bool

(>=) :: PackBytes a -> PackBytes a -> Bool

max :: PackBytes a -> PackBytes a -> PackBytes a

min :: PackBytes a -> PackBytes a -> PackBytes a

Show (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

showsPrec :: Int -> PackBytes a -> ShowS

show :: PackBytes a -> String

showList :: [PackBytes a] -> ShowS

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

Defined in Data.Finitary.PackBytes

Associated Types

type Cardinality (PackBytes a) :: Nat #

Hashable (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

hashWithSalt :: Int -> PackBytes a -> Int #

hash :: PackBytes a -> Int #

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

Defined in Data.Finitary.PackBytes

Methods

sizeOf :: PackBytes a -> Int

alignment :: PackBytes a -> Int

peekElemOff :: Ptr (PackBytes a) -> Int -> IO (PackBytes a)

pokeElemOff :: Ptr (PackBytes a) -> Int -> PackBytes a -> IO ()

peekByteOff :: Ptr b -> Int -> IO (PackBytes a)

pokeByteOff :: Ptr b -> Int -> PackBytes a -> IO ()

peek :: Ptr (PackBytes a) -> IO (PackBytes a)

poke :: Ptr (PackBytes a) -> PackBytes a -> IO ()

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

Defined in Data.Finitary.PackBytes

NFData (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

rnf :: PackBytes a -> ()

Binary (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

Methods

put :: PackBytes a -> Put

get :: Get (PackBytes a)

putList :: [PackBytes a] -> Put

newtype MVector s (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

newtype MVector s (PackBytes a) = MV_PackBytes (MVector s Word8)
newtype Vector (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

newtype Vector (PackBytes a) = V_PackBytes (Vector Word8)
type Cardinality (PackBytes a) Source # 
Instance details

Defined in Data.Finitary.PackBytes

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

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

import Data.Finitary.PackBytes

anInt :: PackBytes Int
anInt = Packed 10

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

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