extensible-0.8: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Bits

Description

Bit-packed records

Synopsis

Documentation

newtype BitProd r (xs :: [k]) (h :: k -> Type) Source #

Bit-vector product. It has similar interface as (:*) but fields are packed into r.

Constructors

BitProd 

Fields

Instances
(Corepresentable p, Comonad (Corep p), Functor f) => Extensible f p (BitProd r :: [k] -> (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type ExtensibleConstr (BitProd r) xs h x :: Constraint Source #

Methods

pieceAt :: ExtensibleConstr (BitProd r) xs h x => Membership xs x -> Optic' p f (BitProd r xs h) (h x) Source #

(Bits r, KnownNat (TotalBits h xs)) => FromBits r (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (BitProd r xs h) :: Nat Source #

Methods

fromBits :: r -> BitProd r xs h Source #

toBits :: BitProd r xs h -> r Source #

Bounded r => Bounded (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

minBound :: BitProd r xs h #

maxBound :: BitProd r xs h #

Enum r => Enum (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

succ :: BitProd r xs h -> BitProd r xs h #

pred :: BitProd r xs h -> BitProd r xs h #

toEnum :: Int -> BitProd r xs h #

fromEnum :: BitProd r xs h -> Int #

enumFrom :: BitProd r xs h -> [BitProd r xs h] #

enumFromThen :: BitProd r xs h -> BitProd r xs h -> [BitProd r xs h] #

enumFromTo :: BitProd r xs h -> BitProd r xs h -> [BitProd r xs h] #

enumFromThenTo :: BitProd r xs h -> BitProd r xs h -> BitProd r xs h -> [BitProd r xs h] #

Eq r => Eq (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

(==) :: BitProd r xs h -> BitProd r xs h -> Bool #

(/=) :: BitProd r xs h -> BitProd r xs h -> Bool #

Ord r => Ord (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

compare :: BitProd r xs h -> BitProd r xs h -> Ordering #

(<) :: BitProd r xs h -> BitProd r xs h -> Bool #

(<=) :: BitProd r xs h -> BitProd r xs h -> Bool #

(>) :: BitProd r xs h -> BitProd r xs h -> Bool #

(>=) :: BitProd r xs h -> BitProd r xs h -> Bool #

max :: BitProd r xs h -> BitProd r xs h -> BitProd r xs h #

min :: BitProd r xs h -> BitProd r xs h -> BitProd r xs h #

(Forall (Instance1 Show h) xs, BitFields r xs h) => Show (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

showsPrec :: Int -> BitProd r xs h -> ShowS #

show :: BitProd r xs h -> String #

showList :: [BitProd r xs h] -> ShowS #

Ix r => Ix (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

range :: (BitProd r xs h, BitProd r xs h) -> [BitProd r xs h] #

index :: (BitProd r xs h, BitProd r xs h) -> BitProd r xs h -> Int #

unsafeIndex :: (BitProd r xs h, BitProd r xs h) -> BitProd r xs h -> Int

inRange :: (BitProd r xs h, BitProd r xs h) -> BitProd r xs h -> Bool #

rangeSize :: (BitProd r xs h, BitProd r xs h) -> Int #

unsafeRangeSize :: (BitProd r xs h, BitProd r xs h) -> Int

Generic (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type Rep (BitProd r xs h) :: Type -> Type #

Methods

from :: BitProd r xs h -> Rep (BitProd r xs h) x #

to :: Rep (BitProd r xs h) x -> BitProd r xs h #

Hashable r => Hashable (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

hashWithSalt :: Int -> BitProd r xs h -> Int #

hash :: BitProd r xs h -> Int #

Storable r => Storable (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Methods

sizeOf :: BitProd r xs h -> Int #

alignment :: BitProd r xs h -> Int #

peekElemOff :: Ptr (BitProd r xs h) -> Int -> IO (BitProd r xs h) #

pokeElemOff :: Ptr (BitProd r xs h) -> Int -> BitProd r xs h -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BitProd r xs h) #

pokeByteOff :: Ptr b -> Int -> BitProd r xs h -> IO () #

peek :: Ptr (BitProd r xs h) -> IO (BitProd r xs h) #

poke :: Ptr (BitProd r xs h) -> BitProd r xs h -> IO () #

type ExtensibleConstr (BitProd r :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Bits

type ExtensibleConstr (BitProd r :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) = (BitFields r xs h, FromBits r (h x))
type Rep (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

type Rep (BitProd r xs h) = D1 (MetaData "BitProd" "Data.Extensible.Bits" "extensible-0.8-BFx4iY1XFYP1mvaDMl3Grp" True) (C1 (MetaCons "BitProd" PrefixI True) (S1 (MetaSel (Just "unBitProd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 r)))
type BitWidth (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

type BitWidth (BitProd r xs h) = TotalBits h xs

class (Bits r, KnownNat (BitWidth a)) => FromBits r a where Source #

Conversion between a value and a bit representation.

Instances of FromBits must satisfy the following laws:

fromBits (x `shiftL` W .|. toBits a) ≡ a
toBits a `shiftR` W == zeroBits

where W is the BitWidth.

Associated Types

type BitWidth a :: Nat Source #

Methods

fromBits :: r -> a Source #

toBits :: a -> r Source #

Instances
FromBits Word64 Bool Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Bool :: Nat Source #

FromBits Word64 Int8 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Int8 :: Nat Source #

FromBits Word64 Int16 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Int16 :: Nat Source #

FromBits Word64 Int32 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Int32 :: Nat Source #

FromBits Word64 Word8 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Word8 :: Nat Source #

FromBits Word64 Word16 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Word16 :: Nat Source #

FromBits Word64 Word32 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Word32 :: Nat Source #

FromBits Word64 Word64 Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth Word64 :: Nat Source #

Bits r => FromBits r () Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth () :: Nat Source #

Methods

fromBits :: r -> () Source #

toBits :: () -> r Source #

FromBits r a => FromBits r (Identity a) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (Identity a) :: Nat Source #

Methods

fromBits :: r -> Identity a Source #

toBits :: Identity a -> r Source #

(FromBits r a, FromBits r b, n ~ (BitWidth a + BitWidth b), n <= BitWidth r, KnownNat n) => FromBits r (a, b) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (a, b) :: Nat Source #

Methods

fromBits :: r -> (a, b) Source #

toBits :: (a, b) -> r Source #

Bits r => FromBits r (Proxy a) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (Proxy a) :: Nat Source #

Methods

fromBits :: r -> Proxy a Source #

toBits :: Proxy a -> r Source #

FromBits r a => FromBits r (Const a b) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (Const a b) :: Nat Source #

Methods

fromBits :: r -> Const a b Source #

toBits :: Const a b -> r Source #

(Bits r, KnownNat (TotalBits h xs)) => FromBits r (BitProd r xs h) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (BitProd r xs h) :: Nat Source #

Methods

fromBits :: r -> BitProd r xs h Source #

toBits :: BitProd r xs h -> r Source #

(Bits r, FromBits r (h (TargetOf x))) => FromBits r (Field h x) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (Field h x) :: Nat Source #

Methods

fromBits :: r -> Field h x Source #

toBits :: Field h x -> r Source #

type family TotalBits h xs where ... Source #

Total BitWidth

Equations

TotalBits h '[] = 0 
TotalBits h (x ': xs) = BitWidth (h x) + TotalBits h xs 

type BitFields r xs h = (FromBits r r, TotalBits h xs <= BitWidth r, Forall (Instance1 (FromBits r) h) xs) Source #

Fields are instances of FromBits and fit in the representation.

blookup :: forall x r xs h. (BitFields r xs h, FromBits r (h x)) => Membership xs x -> BitProd r xs h -> h x Source #

bupdate :: forall x r xs h. (BitFields r xs h, FromBits r (h x)) => Membership xs x -> BitProd r xs h -> h x -> BitProd r xs h Source #

Update a field of a BitProd.

toBitProd :: forall r xs h. BitFields r xs h => (xs :& h) -> BitProd r xs h Source #

Convert a normal extensible record into a bit record.

fromBitProd :: forall r xs h. BitFields r xs h => BitProd r xs h -> xs :& h Source #

Convert a normal extensible record into a bit record.

type BitRecordOf r h xs = BitProd r xs (Field h) Source #

Bit-packed record

type BitRecord r xs = BitRecordOf r Identity xs Source #

Bit-packed record