Copyright | (c) Fumiaki Kinoshita 2018 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Bit-packed records
Synopsis
- newtype BitProd r (h :: k -> *) (xs :: [k]) = BitProd {
- unBitProd :: r
- class (Bits r, KnownNat (BitWidth a)) => FromBits r a where
- type family TotalBits h xs where ...
- type BitFields r h xs = (FromBits r r, TotalBits h xs <= BitWidth r, Forall (Instance1 (FromBits r) h) xs)
- blookup :: forall x r h xs. (BitFields r h xs, FromBits r (h x)) => Membership xs x -> BitProd r h xs -> h x
- bupdate :: forall x r h xs. (BitFields r h xs, FromBits r (h x)) => Membership xs x -> BitProd r h xs -> h x -> BitProd r h xs
- toBitProd :: forall r h xs. BitFields r h xs => (h :* xs) -> BitProd r h xs
- fromBitProd :: forall r h xs. BitFields r h xs => BitProd r h xs -> h :* xs
- type BitRecordOf r h = BitProd r (Field h)
- type BitRecord r = BitRecordOf r Identity
Documentation
newtype BitProd r (h :: k -> *) (xs :: [k]) Source #
Bit-vector product. It has similar interface as (:*)
but fields are packed into r
.
Instances
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
.
Instances
FromBits Word64 Bool Source # | |
FromBits Word64 Int8 Source # | |
FromBits Word64 Int16 Source # | |
FromBits Word64 Int32 Source # | |
FromBits Word64 Word8 Source # | |
FromBits Word64 Word16 Source # | |
FromBits Word64 Word32 Source # | |
FromBits Word64 Word64 Source # | |
Bits r => FromBits r () Source # | |
FromBits r a => FromBits r (Identity a) Source # | |
(FromBits r a, FromBits r b, n ~ (BitWidth a + BitWidth b), n <= BitWidth r, KnownNat n) => FromBits r (a, b) Source # | |
Bits r => FromBits r (Proxy a) Source # | |
FromBits r a => FromBits r (Const a b) Source # | |
(Bits r, KnownNat (TotalBits h xs)) => FromBits r (BitProd r h xs) Source # | |
(Bits r, FromBits r (h (AssocValue x))) => FromBits r (Field h x) Source # | |
type BitFields r h xs = (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 h xs. (BitFields r h xs, FromBits r (h x)) => Membership xs x -> BitProd r h xs -> h x Source #
bupdate :: forall x r h xs. (BitFields r h xs, FromBits r (h x)) => Membership xs x -> BitProd r h xs -> h x -> BitProd r h xs Source #
Update a field of a BitProd
.
toBitProd :: forall r h xs. BitFields r h xs => (h :* xs) -> BitProd r h xs Source #
Convert a normal extensible record into a bit record.
fromBitProd :: forall r h xs. BitFields r h xs => BitProd r h xs -> h :* xs Source #
Convert a normal extensible record into a bit record.
type BitRecordOf r h = BitProd r (Field h) Source #
Bit-packed record
type BitRecord r = BitRecordOf r Identity Source #
Bit-packed record