{-# language CPP #-}
module Vulkan.CStruct  ( ToCStruct(..)
                       , FromCStruct(..)
                       ) where

import Control.Exception.Base (bracket)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Ptr (Ptr)

-- | A class for types which can be marshalled into a C style
-- structure.
class ToCStruct a where
  -- | Allocates a C type structure and all dependencies and passes
  -- it to a continuation. The space is deallocated when this
  -- continuation returns and the C type structure must not be
  -- returned out of it.
  withCStruct :: a -> (Ptr a -> IO b) -> IO b
  withCStruct x :: a
x f :: Ptr a -> IO b
f = Int -> Int -> (Ptr a -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned (ToCStruct a => Int
forall a. ToCStruct a => Int
cStructSize @a) (ToCStruct a => Int
forall a. ToCStruct a => Int
cStructAlignment @a)
    ((Ptr a -> IO b) -> IO b) -> (Ptr a -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr a
p -> Ptr a -> a -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr a
p a
x (Ptr a -> IO b
f Ptr a
p)

  -- | Write a C type struct into some existing memory and run a
  -- continuation. The pointed to structure is not necessarily valid
  -- outside the continuation as additional allocations may have been
  -- made.
  pokeCStruct :: Ptr a -> a -> IO b -> IO b

  -- | Allocate space for an "empty" @a@ and populate any univalued
  -- members with their value.
  withZeroCStruct :: (Ptr a -> IO b) -> IO b
  withZeroCStruct f :: Ptr a -> IO b
f =
    IO (Ptr a) -> (Ptr a -> IO ()) -> (Ptr a -> IO b) -> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr a)
forall a. Int -> IO (Ptr a)
callocBytes @a (ToCStruct a => Int
forall a. ToCStruct a => Int
cStructSize @a)) Ptr a -> IO ()
forall a. Ptr a -> IO ()
free ((Ptr a -> IO b) -> IO b) -> (Ptr a -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr a
p -> Ptr a -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct Ptr a
p (Ptr a -> IO b
f Ptr a
p)

  -- | And populate any univalued members with their value, run a
  -- function and then clean up any allocated resources.
  pokeZeroCStruct :: Ptr a -> IO b -> IO b

  -- | The size of this struct, note that this doesn't account for any
  -- extra pointed-to data
  cStructSize :: Int

  -- | The required memory alignment for this type
  cStructAlignment :: Int


-- | A class for types which can be marshalled from a C style
-- structure.
class FromCStruct a where
  -- | Read an @a@ and any other pointed to data from memory
  peekCStruct :: Ptr a -> IO a