{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE NoStarIsType #-}
module Haskus.Memory.Layout
( LPath (..)
, PathElem (..)
, lPath
, LPathType
, LPathOffset
, LRoot
, (:->)
, (:#>)
, CPrimitive (..)
, CArray (..)
, CUArray (..)
, CStruct (..)
, CUnion (..)
)
where
import Haskus.Utils.Types
data LPath (path :: [PathElem]) = LPath
data PathElem
= LIndex Nat
| LSymbol Symbol
type LRoot = LPath '[]
lPath :: forall e. LPath '[e]
lPath = LPath
type family LPathType p l :: Type
type instance LPathType (LPath '[]) l = l
type family LPathOffset p l :: Nat
type instance LPathOffset (LPath '[]) l = 0
type family (:->) p (s :: Symbol) where
(:->) (LPath xs) s = LPath (Snoc xs ('LSymbol s))
type family (:#>) p (n :: Nat) where
(:#>) (LPath xs) n = LPath (Snoc xs ('LIndex n))
type family CSizeOf a :: Nat
type family CAlignment a :: Nat
data CPrimitive (size :: Nat) (align :: Nat) = CPrimitive
type instance CSizeOf (CPrimitive size align) = size
type instance CAlignment (CPrimitive size align) = align
data CArray (n :: Nat) (a :: k) = CArray
type instance CSizeOf (CArray n a) = n * (CSizeOf a)
type instance CAlignment (CArray n a) = CAlignment a
data CUArray (a :: k) = CUArray
type instance CSizeOf (CUArray a) = TypeError ('Text "Cannot apply SizeOf to an unbounded array")
type instance CAlignment (CUArray a) = CAlignment a
data CStruct (fs :: [Field]) = CStruct
type instance CSizeOf (CStruct fs) = CStructSize fs (CMaxAlignment fs 1) 0
type instance CAlignment (CStruct fs) = CMaxAlignment fs 1
type family CStructSize (xs :: [Field]) al sz where
CStructSize '[] al sz =
sz + PaddingEx (sz `Mod` al) al
CStructSize ('Field s t : fs) al sz = CStructSize fs al
(sz + CSizeOf t + PaddingEx (sz `Mod` CAlignment t) (CAlignment t))
data CUnion (fs :: [Field]) = CUnion
type instance CSizeOf (CUnion fs) = CUnionSize fs (CMaxAlignment fs 1) 0
type instance CAlignment (CUnion fs) = CMaxAlignment fs 1
type family CUnionSize (xs :: [Field]) al sz where
CUnionSize '[] al sz =
sz + PaddingEx (sz `Mod` al) al
CUnionSize ('Field s t : fs) al sz = CUnionSize fs al (Max (CSizeOf t) sz)
data Field = Field Symbol Type
type family PaddingEx (m :: Nat) (a :: Nat) where
PaddingEx 0 a = 0
PaddingEx m a = a - m
type family CMaxAlignment (xs :: [Field]) al where
CMaxAlignment '[] al = al
CMaxAlignment ('Field s t : fs) al =
CMaxAlignment fs (Max al (CAlignment t))