haskus-binary-1.5: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Memory.Layout

Contents

Description

Memory layout

Describe a memory region

Synopsis

Documentation

data LPath (path :: [PathElem]) Source #

Path in a layout

Constructors

LPath 
Instances
type LPathOffset (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathOffset (LPath ([] :: [PathElem])) l = 0
type LPathType (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathType (LPath ([] :: [PathElem])) l = l

data PathElem Source #

Layout path element

Constructors

LIndex Nat

Addressing via a numeric index

LSymbol Symbol

Addressing via a symbol

Instances
type LPathOffset (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathOffset (LPath ([] :: [PathElem])) l = 0
type LPathType (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathType (LPath ([] :: [PathElem])) l = l

lPath :: forall e. LPath '[e] Source #

Index in the layout path

Helper for ``ptr --> lPath @p`` until

type family LPathType p l :: Type Source #

Type obtained when following path p

Instances
type LPathType (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathType (LPath ([] :: [PathElem])) l = l

type family LPathOffset p l :: Nat Source #

Offset obtained when following path p

Instances
type LPathOffset (LPath ([] :: [PathElem])) l Source # 
Instance details

Defined in Haskus.Memory.Layout

type LPathOffset (LPath ([] :: [PathElem])) l = 0

type LRoot = LPath '[] Source #

Layout path root

type family p :-> (s :: Symbol) where ... Source #

Equations

(LPath xs) :-> s = LPath (Snoc xs (LSymbol s)) 

type family p :#> (n :: Nat) where ... Source #

Equations

(LPath xs) :#> n = LPath (Snoc xs (LIndex n)) 

Layouts

data CPrimitive (size :: Nat) (align :: Nat) Source #

Primitives

>>> :kind! CSizeOf (CPrimitive 8 1)
CSizeOf (CPrimitive 8 1) :: Nat
= 8
>>> :kind! CAlignment (CPrimitive 8 2)
CAlignment (CPrimitive 8 2) :: Nat
= 2

Constructors

CPrimitive 

data CArray (n :: Nat) (a :: k) Source #

Array

>>> type S = CArray 10 (CPrimitive 8 8)
>>> :kind! CSizeOf S
CSizeOf S :: Nat
= 80
>>> :kind! CAlignment S
CAlignment S :: Nat
= 8

Constructors

CArray 

data CUArray (a :: k) Source #

Unbounded array

>>> type S = CUArray (CPrimitive 8 8)
>>> :kind! CSizeOf S
CSizeOf S :: Nat
= (TypeError ...)
>>> :kind! CAlignment S
CAlignment S :: Nat
= 8

Constructors

CUArray 

data CStruct (fs :: [Field]) Source #

Struct

>>> type S = CStruct ['Field "i8" (CPrimitive 1 1), 'Field "i32" (CPrimitive 4 4)]
>>> :kind! CSizeOf S
CSizeOf S :: Nat
= 8
>>> :kind! CAlignment S
CAlignment S :: Nat
= 4

Constructors

CStruct 

data CUnion (fs :: [Field]) Source #

Union

>>> type S = CUnion ['Field "i8" (CPrimitive 1 1), 'Field "i32" (CPrimitive 4 4)]
>>> :kind! CSizeOf S
CSizeOf S :: Nat
= 4
>>> :kind! CAlignment S
CAlignment S :: Nat
= 4

Constructors

CUnion