haskus-binary-1.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Record

Description

Record (similar to C struct)

Synopsis

Documentation

data Record (fields :: [*]) Source #

Record

Instances
(HFoldr' Extract (Record fs, HList ([] :: [*])) fs (Record fs, HList fs), Show (HList fs)) => Show (Record fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Record

Methods

showsPrec :: Int -> Record fs -> ShowS #

show :: Record fs -> String #

showList :: [Record fs] -> ShowS #

(s ~ FullRecordSize fs, KnownNat s) => StaticStorable (Record fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Record

Associated Types

type SizeOf (Record fs) :: Nat Source #

type Alignment (Record fs) :: Nat Source #

Methods

staticPeekIO :: Ptr (Record fs) -> IO (Record fs) Source #

staticPokeIO :: Ptr (Record fs) -> Record fs -> IO () Source #

type SizeOf (Record fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Record

type SizeOf (Record fs)
type Alignment (Record fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Record

type Alignment (Record fs)

data Field (name :: Symbol) typ Source #

Field

type family RecordSize (fs :: [*]) (sz :: Nat) where ... Source #

Get record size without the ending padding bytes

Equations

RecordSize '[] sz = sz 
RecordSize (Field name typ ': fs) sz = RecordSize fs ((sz + Padding sz typ) + SizeOf typ) 

type family Alignment a :: Nat Source #

Alignment requirement (in bytes)

Instances
type Alignment Int8 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Int8 = 1
type Alignment Int16 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Int16 = 2
type Alignment Int32 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Int32 = 4
type Alignment Int64 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Int64 = 8
type Alignment Word8 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Word8 = 1
type Alignment Word16 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Word16 = 2
type Alignment Word32 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Word32 = 4
type Alignment Word64 Source # 
Instance details

Defined in Haskus.Format.Binary.Storable

type Alignment Word64 = 8
type Alignment (Union fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Union

type Alignment (Union fs)
type Alignment (Record fs) Source # 
Instance details

Defined in Haskus.Format.Binary.Record

type Alignment (Record fs)
type Alignment (AsLittleEndian a) Source # 
Instance details

Defined in Haskus.Format.Binary.Endianness

type Alignment (AsBigEndian a) Source # 
Instance details

Defined in Haskus.Format.Binary.Endianness

type Alignment (EnumField b a) Source # 
Instance details

Defined in Haskus.Format.Binary.Enum

type Alignment (Vector n a) Source # 
Instance details

Defined in Haskus.Format.Binary.Vector

type Alignment (Vector n a) = Alignment a

type family Modulo (a :: Nat) (b :: Nat) :: Nat where ... #

Modulo

Equations

Modulo a b = Modulo' (a <=? b) a b 

data Path (fs :: [Symbol]) Source #

recordSize :: forall fs. KnownNat (FullRecordSize fs) => Record fs -> Word Source #

Get record size

recordAlignment :: forall fs. KnownNat (RecordAlignment fs 1) => Record fs -> Word Source #

Get record alignment

recordField :: forall (name :: Symbol) a fs. (KnownNat (FieldOffset name fs 0), a ~ FieldType name fs, StaticStorable a) => Record fs -> a Source #

Get a field

recordFieldOffset :: forall (name :: Symbol) fs. KnownNat (FieldOffset name fs 0) => Record fs -> Int Source #

Get a field offset

recordFieldPath :: forall path a fs o. (o ~ FieldPathOffset fs path 0, a ~ FieldPathType fs path, KnownNat o, StaticStorable a) => Path path -> Record fs -> a Source #

Get a field from its path

recordFieldPathOffset :: forall path fs o. (o ~ FieldPathOffset fs path 0, KnownNat o) => Path path -> Record fs -> Int Source #

Get a field offset from its path

recordToList :: forall fs. HFoldr' Extract (Record fs, HList '[]) fs (Record fs, HList fs) => Record fs -> HList fs Source #

Convert a record into a HList