{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_pipeline_executable_properties ( getPipelineExecutablePropertiesKHR
, getPipelineExecutableStatisticsKHR
, getPipelineExecutableInternalRepresentationsKHR
, PhysicalDevicePipelineExecutablePropertiesFeaturesKHR(..)
, PipelineInfoKHR(..)
, PipelineExecutablePropertiesKHR(..)
, PipelineExecutableInfoKHR(..)
, PipelineExecutableStatisticKHR(..)
, PipelineExecutableInternalRepresentationKHR(..)
, PipelineExecutableStatisticValueKHR(..)
, peekPipelineExecutableStatisticValueKHR
, PipelineExecutableStatisticFormatKHR( PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR
, PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR
, PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR
, PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR
, ..
)
, KHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION
, pattern KHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION
, KHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME
, pattern KHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME
) where
import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.ByteString (packCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
import Data.Vector (generateM)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CDouble)
import Foreign.C.Types (CDouble(CDouble))
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(CSize))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Data.Int (Int64)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Data.Word (Word64)
import Text.Read.Lex (Lexeme(Ident))
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Utils (pokeFixedLengthNullTerminatedByteString)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineExecutableInternalRepresentationsKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineExecutablePropertiesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineExecutableStatisticsKHR))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.APIConstants (MAX_DESCRIPTION_SIZE)
import Vulkan.Core10.Handles (Pipeline)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_EXECUTABLE_PROPERTIES_FEATURES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INTERNAL_REPRESENTATION_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_EXECUTABLE_PROPERTIES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_EXECUTABLE_STATISTIC_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPipelineExecutablePropertiesKHR
:: FunPtr (Ptr Device_T -> Ptr PipelineInfoKHR -> Ptr Word32 -> Ptr PipelineExecutablePropertiesKHR -> IO Result) -> Ptr Device_T -> Ptr PipelineInfoKHR -> Ptr Word32 -> Ptr PipelineExecutablePropertiesKHR -> IO Result
getPipelineExecutablePropertiesKHR :: forall io . MonadIO io => Device -> PipelineInfoKHR -> io (Result, ("properties" ::: Vector PipelineExecutablePropertiesKHR))
getPipelineExecutablePropertiesKHR :: Device
-> PipelineInfoKHR
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
getPipelineExecutablePropertiesKHR device :: Device
device pipelineInfo :: PipelineInfoKHR
pipelineInfo = IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> (ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> io
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPipelineExecutablePropertiesKHRPtr :: FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
vkGetPipelineExecutablePropertiesKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
pVkGetPipelineExecutablePropertiesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
())
-> IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
vkGetPipelineExecutablePropertiesKHRPtr FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPipelineExecutablePropertiesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPipelineExecutablePropertiesKHR' :: Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result
vkGetPipelineExecutablePropertiesKHR' = FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
-> Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result
mkVkGetPipelineExecutablePropertiesKHR FunPtr
(Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result)
vkGetPipelineExecutablePropertiesKHRPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pPipelineInfo" ::: Ptr PipelineInfoKHR
pPipelineInfo <- ((("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pPipelineInfo" ::: Ptr PipelineInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pPipelineInfo" ::: Ptr PipelineInfoKHR))
-> ((("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pPipelineInfo" ::: Ptr PipelineInfoKHR)
forall a b. (a -> b) -> a -> b
$ PipelineInfoKHR
-> (("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineInfoKHR
pipelineInfo)
"pExecutableCount" ::: Ptr Word32
pPExecutableCount <- ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pExecutableCount" ::: Ptr Word32))
-> ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pExecutableCount" ::: Ptr Word32)
-> (("pExecutableCount" ::: Ptr Word32) -> IO ())
-> (("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pExecutableCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pExecutableCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result)
-> IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result
vkGetPipelineExecutablePropertiesKHR' Ptr Device_T
device' "pPipelineInfo" ::: Ptr PipelineInfoKHR
pPipelineInfo ("pExecutableCount" ::: Ptr Word32
pPExecutableCount) ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
forall a. Ptr a
nullPtr)
IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
())
-> IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Word32
pExecutableCount <- IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPExecutableCount
"pProperties" ::: Ptr PipelineExecutablePropertiesKHR
pPProperties <- ((("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pProperties" ::: Ptr PipelineExecutablePropertiesKHR))
-> ((("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO ())
-> (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
forall a. Int -> IO (Ptr a)
callocBytes @PipelineExecutablePropertiesKHR ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pExecutableCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 536)) ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR) -> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
())
-> [Int]
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
())
-> ((()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
pPProperties ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 536) :: Ptr PipelineExecutablePropertiesKHR) (IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ((()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> (()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> ()
-> IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pExecutableCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
Result
r' <- IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result)
-> IO Result
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO Result
vkGetPipelineExecutablePropertiesKHR' Ptr Device_T
device' "pPipelineInfo" ::: Ptr PipelineInfoKHR
pPipelineInfo ("pExecutableCount" ::: Ptr Word32
pPExecutableCount) (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
pPProperties))
IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
())
-> IO ()
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
Word32
pExecutableCount' <- IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPExecutableCount
"properties" ::: Vector PipelineExecutablePropertiesKHR
pProperties' <- IO ("properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("properties" ::: Vector PipelineExecutablePropertiesKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("properties" ::: Vector PipelineExecutablePropertiesKHR))
-> IO ("properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
("properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO PipelineExecutablePropertiesKHR)
-> IO ("properties" ::: Vector PipelineExecutablePropertiesKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pExecutableCount')) (\i :: Int
i -> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO PipelineExecutablePropertiesKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineExecutablePropertiesKHR ((("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
pPProperties) ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (536 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineExecutablePropertiesKHR)))
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR))
-> (Result,
"properties" ::: Vector PipelineExecutablePropertiesKHR)
-> ContT
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
IO
(Result, "properties" ::: Vector PipelineExecutablePropertiesKHR)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "properties" ::: Vector PipelineExecutablePropertiesKHR
pProperties')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPipelineExecutableStatisticsKHR
:: FunPtr (Ptr Device_T -> Ptr PipelineExecutableInfoKHR -> Ptr Word32 -> Ptr PipelineExecutableStatisticKHR -> IO Result) -> Ptr Device_T -> Ptr PipelineExecutableInfoKHR -> Ptr Word32 -> Ptr PipelineExecutableStatisticKHR -> IO Result
getPipelineExecutableStatisticsKHR :: forall io . MonadIO io => Device -> PipelineExecutableInfoKHR -> io (Result, ("statistics" ::: Vector PipelineExecutableStatisticKHR))
getPipelineExecutableStatisticsKHR :: Device
-> PipelineExecutableInfoKHR
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
getPipelineExecutableStatisticsKHR device :: Device
device executableInfo :: PipelineExecutableInfoKHR
executableInfo = IO (Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> (ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> io
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPipelineExecutableStatisticsKHRPtr :: FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
vkGetPipelineExecutableStatisticsKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
pVkGetPipelineExecutableStatisticsKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
())
-> IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
vkGetPipelineExecutableStatisticsKHRPtr FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPipelineExecutableStatisticsKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPipelineExecutableStatisticsKHR' :: Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result
vkGetPipelineExecutableStatisticsKHR' = FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
-> Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result
mkVkGetPipelineExecutableStatisticsKHR FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result)
vkGetPipelineExecutableStatisticsKHRPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo <- ((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR))
-> ((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
forall a b. (a -> b) -> a -> b
$ PipelineExecutableInfoKHR
-> (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineExecutableInfoKHR
executableInfo)
"pExecutableCount" ::: Ptr Word32
pPStatisticCount <- ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableCount" ::: Ptr Word32))
-> ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pExecutableCount" ::: Ptr Word32)
-> (("pExecutableCount" ::: Ptr Word32) -> IO ())
-> (("pExecutableCount" ::: Ptr Word32)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pExecutableCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pExecutableCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result)
-> IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result
vkGetPipelineExecutableStatisticsKHR' Ptr Device_T
device' "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo ("pExecutableCount" ::: Ptr Word32
pPStatisticCount) ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
forall a. Ptr a
nullPtr)
IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
())
-> IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Word32
pStatisticCount <- IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPStatisticCount
"pStatistics" ::: Ptr PipelineExecutableStatisticKHR
pPStatistics <- ((("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pStatistics" ::: Ptr PipelineExecutableStatisticKHR))
-> ((("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO ())
-> (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
forall a. Int -> IO (Ptr a)
callocBytes @PipelineExecutableStatisticKHR ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pStatisticCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 544)) ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
())
-> [Int]
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
())
-> ((()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
pPStatistics ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 544) :: Ptr PipelineExecutableStatisticKHR) (IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ((()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> (()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> ()
-> IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pStatisticCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
Result
r' <- IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result)
-> IO Result
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO Result
vkGetPipelineExecutableStatisticsKHR' Ptr Device_T
device' "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo ("pExecutableCount" ::: Ptr Word32
pPStatisticCount) (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
pPStatistics))
IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
())
-> IO ()
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
Word32
pStatisticCount' <- IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPStatisticCount
"statistics" ::: Vector PipelineExecutableStatisticKHR
pStatistics' <- IO ("statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("statistics" ::: Vector PipelineExecutableStatisticKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("statistics" ::: Vector PipelineExecutableStatisticKHR))
-> IO ("statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
("statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO PipelineExecutableStatisticKHR)
-> IO ("statistics" ::: Vector PipelineExecutableStatisticKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pStatisticCount')) (\i :: Int
i -> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO PipelineExecutableStatisticKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineExecutableStatisticKHR ((("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
pPStatistics) ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (544 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineExecutableStatisticKHR)))
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR))
-> (Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
-> ContT
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
IO
(Result, "statistics" ::: Vector PipelineExecutableStatisticKHR)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "statistics" ::: Vector PipelineExecutableStatisticKHR
pStatistics')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPipelineExecutableInternalRepresentationsKHR
:: FunPtr (Ptr Device_T -> Ptr PipelineExecutableInfoKHR -> Ptr Word32 -> Ptr PipelineExecutableInternalRepresentationKHR -> IO Result) -> Ptr Device_T -> Ptr PipelineExecutableInfoKHR -> Ptr Word32 -> Ptr PipelineExecutableInternalRepresentationKHR -> IO Result
getPipelineExecutableInternalRepresentationsKHR :: forall io . MonadIO io => Device -> PipelineExecutableInfoKHR -> io (Result, ("internalRepresentations" ::: Vector PipelineExecutableInternalRepresentationKHR))
getPipelineExecutableInternalRepresentationsKHR :: Device
-> PipelineExecutableInfoKHR
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
getPipelineExecutableInternalRepresentationsKHR device :: Device
device executableInfo :: PipelineExecutableInfoKHR
executableInfo = IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> (ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> io
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPipelineExecutableInternalRepresentationsKHRPtr :: FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
vkGetPipelineExecutableInternalRepresentationsKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
pVkGetPipelineExecutableInternalRepresentationsKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
())
-> IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
vkGetPipelineExecutableInternalRepresentationsKHRPtr FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPipelineExecutableInternalRepresentationsKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPipelineExecutableInternalRepresentationsKHR' :: Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result
vkGetPipelineExecutableInternalRepresentationsKHR' = FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
-> Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result
mkVkGetPipelineExecutableInternalRepresentationsKHR FunPtr
(Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result)
vkGetPipelineExecutableInternalRepresentationsKHRPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo <- ((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR))
-> ((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
forall a b. (a -> b) -> a -> b
$ PipelineExecutableInfoKHR
-> (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineExecutableInfoKHR
executableInfo)
"pExecutableCount" ::: Ptr Word32
pPInternalRepresentationCount <- ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableCount" ::: Ptr Word32))
-> ((("pExecutableCount" ::: Ptr Word32)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pExecutableCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pExecutableCount" ::: Ptr Word32)
-> (("pExecutableCount" ::: Ptr Word32) -> IO ())
-> (("pExecutableCount" ::: Ptr Word32)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pExecutableCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pExecutableCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result)
-> IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result
vkGetPipelineExecutableInternalRepresentationsKHR' Ptr Device_T
device' "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo ("pExecutableCount" ::: Ptr Word32
pPInternalRepresentationCount) ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
forall a. Ptr a
nullPtr)
IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
())
-> IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Word32
pInternalRepresentationCount <- IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPInternalRepresentationCount
"pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
pPInternalRepresentations <- ((("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR))
-> ((("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
forall a b. (a -> b) -> a -> b
$ IO
("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO ())
-> (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
forall a. Int -> IO (Ptr a)
callocBytes @PipelineExecutableInternalRepresentationKHR ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pInternalRepresentationCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 552)) ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
())
-> [Int]
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
())
-> ((()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
pPInternalRepresentations ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int
-> "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 552) :: Ptr PipelineExecutableInternalRepresentationKHR) (IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ((()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> (()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> ()
-> IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pInternalRepresentationCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
Result
r' <- IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result)
-> IO Result
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> ("pExecutableCount" ::: Ptr Word32)
-> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO Result
vkGetPipelineExecutableInternalRepresentationsKHR' Ptr Device_T
device' "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
pExecutableInfo ("pExecutableCount" ::: Ptr Word32
pPInternalRepresentationCount) (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
pPInternalRepresentations))
IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
())
-> IO ()
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
Word32
pInternalRepresentationCount' <- IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32)
-> IO Word32
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pExecutableCount" ::: Ptr Word32
pPInternalRepresentationCount
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR
pInternalRepresentations' <- IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO PipelineExecutableInternalRepresentationKHR)
-> IO
("internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pInternalRepresentationCount')) (\i :: Int
i -> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO PipelineExecutableInternalRepresentationKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineExecutableInternalRepresentationKHR ((("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
pPInternalRepresentations) ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int
-> "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (552 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineExecutableInternalRepresentationKHR)))
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR))
-> (Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
-> ContT
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
IO
(Result,
"internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "internalRepresentations"
::: Vector PipelineExecutableInternalRepresentationKHR
pInternalRepresentations')
data PhysicalDevicePipelineExecutablePropertiesFeaturesKHR = PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
{
PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> Bool
pipelineExecutableInfo :: Bool }
deriving (Typeable)
deriving instance Show PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
instance ToCStruct PhysicalDevicePipelineExecutablePropertiesFeaturesKHR where
withCStruct :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> (Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b)
-> IO b
withCStruct x :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
x f :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> IO b
f = Int
-> Int
-> (Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b)
-> IO b)
-> (Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p -> Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
x (Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> IO b
f Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p)
pokeCStruct :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b
-> IO b
pokeCStruct p :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p PhysicalDevicePipelineExecutablePropertiesFeaturesKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_EXECUTABLE_PROPERTIES_FEATURES_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
pipelineExecutableInfo))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_EXECUTABLE_PROPERTIES_FEATURES_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevicePipelineExecutablePropertiesFeaturesKHR where
peekCStruct :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
peekCStruct p :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p = do
Bool32
pipelineExecutableInfo <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
p Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR)
-> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
(Bool32 -> Bool
bool32ToBool Bool32
pipelineExecutableInfo)
instance Storable PhysicalDevicePipelineExecutablePropertiesFeaturesKHR where
sizeOf :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> Int
sizeOf ~PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
_ = 24
alignment :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> Int
alignment ~PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
_ = 8
peek :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
peek = Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR -> IO ()
poke ptr :: Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
ptr poked :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
poked = Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
ptr PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePipelineExecutablePropertiesFeaturesKHR where
zero :: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
zero = Bool -> PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
PhysicalDevicePipelineExecutablePropertiesFeaturesKHR
Bool
forall a. Zero a => a
zero
data PipelineInfoKHR = PipelineInfoKHR
{
PipelineInfoKHR -> Pipeline
pipeline :: Pipeline }
deriving (Typeable)
deriving instance Show PipelineInfoKHR
instance ToCStruct PipelineInfoKHR where
withCStruct :: PipelineInfoKHR
-> (("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b) -> IO b
withCStruct x :: PipelineInfoKHR
x f :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b
f = Int
-> Int
-> (("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b) -> IO b)
-> (("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pPipelineInfo" ::: Ptr PipelineInfoKHR
p -> ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> PipelineInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pPipelineInfo" ::: Ptr PipelineInfoKHR
p PipelineInfoKHR
x (("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b
f "pPipelineInfo" ::: Ptr PipelineInfoKHR
p)
pokeCStruct :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> PipelineInfoKHR -> IO b -> IO b
pokeCStruct p :: "pPipelineInfo" ::: Ptr PipelineInfoKHR
p PipelineInfoKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INFO_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline)) (Pipeline
pipeline)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO b -> IO b
pokeZeroCStruct p :: "pPipelineInfo" ::: Ptr PipelineInfoKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INFO_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline)) (Pipeline
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineInfoKHR where
peekCStruct :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO PipelineInfoKHR
peekCStruct p :: "pPipelineInfo" ::: Ptr PipelineInfoKHR
p = do
Pipeline
pipeline <- Ptr Pipeline -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline (("pPipelineInfo" ::: Ptr PipelineInfoKHR
p ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline))
PipelineInfoKHR -> IO PipelineInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineInfoKHR -> IO PipelineInfoKHR)
-> PipelineInfoKHR -> IO PipelineInfoKHR
forall a b. (a -> b) -> a -> b
$ Pipeline -> PipelineInfoKHR
PipelineInfoKHR
Pipeline
pipeline
instance Storable PipelineInfoKHR where
sizeOf :: PipelineInfoKHR -> Int
sizeOf ~PipelineInfoKHR
_ = 24
alignment :: PipelineInfoKHR -> Int
alignment ~PipelineInfoKHR
_ = 8
peek :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO PipelineInfoKHR
peek = ("pPipelineInfo" ::: Ptr PipelineInfoKHR) -> IO PipelineInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> PipelineInfoKHR -> IO ()
poke ptr :: "pPipelineInfo" ::: Ptr PipelineInfoKHR
ptr poked :: PipelineInfoKHR
poked = ("pPipelineInfo" ::: Ptr PipelineInfoKHR)
-> PipelineInfoKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pPipelineInfo" ::: Ptr PipelineInfoKHR
ptr PipelineInfoKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineInfoKHR where
zero :: PipelineInfoKHR
zero = Pipeline -> PipelineInfoKHR
PipelineInfoKHR
Pipeline
forall a. Zero a => a
zero
data PipelineExecutablePropertiesKHR = PipelineExecutablePropertiesKHR
{
PipelineExecutablePropertiesKHR -> ShaderStageFlags
stages :: ShaderStageFlags
,
PipelineExecutablePropertiesKHR -> ByteString
name :: ByteString
,
PipelineExecutablePropertiesKHR -> ByteString
description :: ByteString
,
PipelineExecutablePropertiesKHR -> Word32
subgroupSize :: Word32
}
deriving (Typeable)
deriving instance Show PipelineExecutablePropertiesKHR
instance ToCStruct PipelineExecutablePropertiesKHR where
withCStruct :: PipelineExecutablePropertiesKHR
-> (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO b)
-> IO b
withCStruct x :: PipelineExecutablePropertiesKHR
x f :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 536 8 ((("pProperties" ::: Ptr PipelineExecutablePropertiesKHR) -> IO b)
-> IO b)
-> (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p -> ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> PipelineExecutablePropertiesKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p PipelineExecutablePropertiesKHR
x (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR) -> IO b
f "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p)
pokeCStruct :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> PipelineExecutablePropertiesKHR -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p PipelineExecutablePropertiesKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_PROPERTIES_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags)) (ShaderStageFlags
stages)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
name)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
description)
("pExecutableCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr Word32)) (Word32
subgroupSize)
IO b
f
cStructSize :: Int
cStructSize = 536
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_PROPERTIES_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags)) (ShaderStageFlags
forall a. Zero a => a
zero)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
("pExecutableCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineExecutablePropertiesKHR where
peekCStruct :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO PipelineExecutablePropertiesKHR
peekCStruct p :: "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p = do
ShaderStageFlags
stages <- Ptr ShaderStageFlags -> IO ShaderStageFlags
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags))
ByteString
name <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
ByteString
description <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
Word32
subgroupSize <- ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr PipelineExecutablePropertiesKHR
p ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr Word32))
PipelineExecutablePropertiesKHR
-> IO PipelineExecutablePropertiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineExecutablePropertiesKHR
-> IO PipelineExecutablePropertiesKHR)
-> PipelineExecutablePropertiesKHR
-> IO PipelineExecutablePropertiesKHR
forall a b. (a -> b) -> a -> b
$ ShaderStageFlags
-> ByteString
-> ByteString
-> Word32
-> PipelineExecutablePropertiesKHR
PipelineExecutablePropertiesKHR
ShaderStageFlags
stages ByteString
name ByteString
description Word32
subgroupSize
instance Storable PipelineExecutablePropertiesKHR where
sizeOf :: PipelineExecutablePropertiesKHR -> Int
sizeOf ~PipelineExecutablePropertiesKHR
_ = 536
alignment :: PipelineExecutablePropertiesKHR -> Int
alignment ~PipelineExecutablePropertiesKHR
_ = 8
peek :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO PipelineExecutablePropertiesKHR
peek = ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> IO PipelineExecutablePropertiesKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> PipelineExecutablePropertiesKHR -> IO ()
poke ptr :: "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
ptr poked :: PipelineExecutablePropertiesKHR
poked = ("pProperties" ::: Ptr PipelineExecutablePropertiesKHR)
-> PipelineExecutablePropertiesKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr PipelineExecutablePropertiesKHR
ptr PipelineExecutablePropertiesKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineExecutablePropertiesKHR where
zero :: PipelineExecutablePropertiesKHR
zero = ShaderStageFlags
-> ByteString
-> ByteString
-> Word32
-> PipelineExecutablePropertiesKHR
PipelineExecutablePropertiesKHR
ShaderStageFlags
forall a. Zero a => a
zero
ByteString
forall a. Monoid a => a
mempty
ByteString
forall a. Monoid a => a
mempty
Word32
forall a. Zero a => a
zero
data PipelineExecutableInfoKHR = PipelineExecutableInfoKHR
{
PipelineExecutableInfoKHR -> Pipeline
pipeline :: Pipeline
,
PipelineExecutableInfoKHR -> Word32
executableIndex :: Word32
}
deriving (Typeable)
deriving instance Show PipelineExecutableInfoKHR
instance ToCStruct PipelineExecutableInfoKHR where
withCStruct :: PipelineExecutableInfoKHR
-> (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b)
-> IO b
withCStruct x :: PipelineExecutableInfoKHR
x f :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b
f = Int
-> Int
-> (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b)
-> IO b)
-> (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p -> ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> PipelineExecutableInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p PipelineExecutableInfoKHR
x (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR) -> IO b
f "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p)
pokeCStruct :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> PipelineExecutableInfoKHR -> IO b -> IO b
pokeCStruct p :: "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p PipelineExecutableInfoKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INFO_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline)) (Pipeline
pipeline)
("pExecutableCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
executableIndex)
IO b
f
cStructSize :: Int
cStructSize = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INFO_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Pipeline -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline)) (Pipeline
forall a. Zero a => a
zero)
("pExecutableCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineExecutableInfoKHR where
peekCStruct :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO PipelineExecutableInfoKHR
peekCStruct p :: "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p = do
Pipeline
pipeline <- Ptr Pipeline -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Pipeline))
Word32
executableIndex <- ("pExecutableCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
p ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> Int -> "pExecutableCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
PipelineExecutableInfoKHR -> IO PipelineExecutableInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineExecutableInfoKHR -> IO PipelineExecutableInfoKHR)
-> PipelineExecutableInfoKHR -> IO PipelineExecutableInfoKHR
forall a b. (a -> b) -> a -> b
$ Pipeline -> Word32 -> PipelineExecutableInfoKHR
PipelineExecutableInfoKHR
Pipeline
pipeline Word32
executableIndex
instance Storable PipelineExecutableInfoKHR where
sizeOf :: PipelineExecutableInfoKHR -> Int
sizeOf ~PipelineExecutableInfoKHR
_ = 32
alignment :: PipelineExecutableInfoKHR -> Int
alignment ~PipelineExecutableInfoKHR
_ = 8
peek :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO PipelineExecutableInfoKHR
peek = ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> IO PipelineExecutableInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> PipelineExecutableInfoKHR -> IO ()
poke ptr :: "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
ptr poked :: PipelineExecutableInfoKHR
poked = ("pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR)
-> PipelineExecutableInfoKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pExecutableInfo" ::: Ptr PipelineExecutableInfoKHR
ptr PipelineExecutableInfoKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineExecutableInfoKHR where
zero :: PipelineExecutableInfoKHR
zero = Pipeline -> Word32 -> PipelineExecutableInfoKHR
PipelineExecutableInfoKHR
Pipeline
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
data PipelineExecutableStatisticKHR = PipelineExecutableStatisticKHR
{
PipelineExecutableStatisticKHR -> ByteString
name :: ByteString
,
PipelineExecutableStatisticKHR -> ByteString
description :: ByteString
,
PipelineExecutableStatisticKHR
-> PipelineExecutableStatisticFormatKHR
format :: PipelineExecutableStatisticFormatKHR
,
PipelineExecutableStatisticKHR
-> PipelineExecutableStatisticValueKHR
value :: PipelineExecutableStatisticValueKHR
}
deriving (Typeable)
deriving instance Show PipelineExecutableStatisticKHR
instance ToCStruct PipelineExecutableStatisticKHR where
withCStruct :: PipelineExecutableStatisticKHR
-> (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b)
-> IO b
withCStruct x :: PipelineExecutableStatisticKHR
x f :: ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b
f = Int
-> Int
-> (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 544 8 ((("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b)
-> IO b)
-> (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p -> ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> PipelineExecutableStatisticKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p PipelineExecutableStatisticKHR
x (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR) -> IO b
f "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p)
pokeCStruct :: ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> PipelineExecutableStatisticKHR -> IO b -> IO b
pokeCStruct p :: "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p PipelineExecutableStatisticKHR{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_STATISTIC_KHR)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
name)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
description)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticFormatKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr PipelineExecutableStatisticFormatKHR)) (PipelineExecutableStatisticFormatKHR
format)
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticValueKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticValueKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr PipelineExecutableStatisticValueKHR)) (PipelineExecutableStatisticValueKHR
value) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 544
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_STATISTIC_KHR)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticFormatKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr PipelineExecutableStatisticFormatKHR)) (PipelineExecutableStatisticFormatKHR
forall a. Zero a => a
zero)
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticValueKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticValueKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr PipelineExecutableStatisticValueKHR)) (PipelineExecutableStatisticValueKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct PipelineExecutableStatisticKHR where
peekCStruct :: ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> IO PipelineExecutableStatisticKHR
peekCStruct p :: "pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p = do
ByteString
name <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
ByteString
description <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
PipelineExecutableStatisticFormatKHR
format <- Ptr PipelineExecutableStatisticFormatKHR
-> IO PipelineExecutableStatisticFormatKHR
forall a. Storable a => Ptr a -> IO a
peek @PipelineExecutableStatisticFormatKHR (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticFormatKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr PipelineExecutableStatisticFormatKHR))
PipelineExecutableStatisticValueKHR
value <- PipelineExecutableStatisticFormatKHR
-> Ptr PipelineExecutableStatisticValueKHR
-> IO PipelineExecutableStatisticValueKHR
peekPipelineExecutableStatisticValueKHR PipelineExecutableStatisticFormatKHR
format (("pStatistics" ::: Ptr PipelineExecutableStatisticKHR
p ("pStatistics" ::: Ptr PipelineExecutableStatisticKHR)
-> Int -> Ptr PipelineExecutableStatisticValueKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr PipelineExecutableStatisticValueKHR))
PipelineExecutableStatisticKHR -> IO PipelineExecutableStatisticKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineExecutableStatisticKHR
-> IO PipelineExecutableStatisticKHR)
-> PipelineExecutableStatisticKHR
-> IO PipelineExecutableStatisticKHR
forall a b. (a -> b) -> a -> b
$ ByteString
-> ByteString
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticKHR
PipelineExecutableStatisticKHR
ByteString
name ByteString
description PipelineExecutableStatisticFormatKHR
format PipelineExecutableStatisticValueKHR
value
instance Zero PipelineExecutableStatisticKHR where
zero :: PipelineExecutableStatisticKHR
zero = ByteString
-> ByteString
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticKHR
PipelineExecutableStatisticKHR
ByteString
forall a. Monoid a => a
mempty
ByteString
forall a. Monoid a => a
mempty
PipelineExecutableStatisticFormatKHR
forall a. Zero a => a
zero
PipelineExecutableStatisticValueKHR
forall a. Zero a => a
zero
data PipelineExecutableInternalRepresentationKHR = PipelineExecutableInternalRepresentationKHR
{
PipelineExecutableInternalRepresentationKHR -> ByteString
name :: ByteString
,
PipelineExecutableInternalRepresentationKHR -> ByteString
description :: ByteString
,
PipelineExecutableInternalRepresentationKHR -> Bool
isText :: Bool
,
PipelineExecutableInternalRepresentationKHR -> Word64
dataSize :: Word64
,
PipelineExecutableInternalRepresentationKHR -> Ptr ()
data' :: Ptr ()
}
deriving (Typeable)
deriving instance Show PipelineExecutableInternalRepresentationKHR
instance ToCStruct PipelineExecutableInternalRepresentationKHR where
withCStruct :: PipelineExecutableInternalRepresentationKHR
-> (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b)
-> IO b
withCStruct x :: PipelineExecutableInternalRepresentationKHR
x f :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b
f = Int
-> Int
-> (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 552 8 ((("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b)
-> IO b)
-> (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p -> ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> PipelineExecutableInternalRepresentationKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p PipelineExecutableInternalRepresentationKHR
x (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b
f "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p)
pokeCStruct :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> PipelineExecutableInternalRepresentationKHR -> IO b -> IO b
pokeCStruct p :: "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p PipelineExecutableInternalRepresentationKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INTERNAL_REPRESENTATION_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
name)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
description)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
isText))
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
dataSize))
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 544 :: Ptr (Ptr ()))) (Ptr ()
data')
IO b
f
cStructSize :: Int
cStructSize = 552
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INTERNAL_REPRESENTATION_KHR)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PipelineExecutableInternalRepresentationKHR where
peekCStruct :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO PipelineExecutableInternalRepresentationKHR
peekCStruct p :: "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p = do
ByteString
name <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
ByteString
description <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr (FixedArray MAX_DESCRIPTION_SIZE CChar))))
Bool32
isText <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 528 :: Ptr Bool32))
CSize
dataSize <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr CSize))
Ptr ()
pData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
p ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 544 :: Ptr (Ptr ())))
PipelineExecutableInternalRepresentationKHR
-> IO PipelineExecutableInternalRepresentationKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineExecutableInternalRepresentationKHR
-> IO PipelineExecutableInternalRepresentationKHR)
-> PipelineExecutableInternalRepresentationKHR
-> IO PipelineExecutableInternalRepresentationKHR
forall a b. (a -> b) -> a -> b
$ ByteString
-> ByteString
-> Bool
-> Word64
-> Ptr ()
-> PipelineExecutableInternalRepresentationKHR
PipelineExecutableInternalRepresentationKHR
ByteString
name ByteString
description (Bool32 -> Bool
bool32ToBool Bool32
isText) ((\(CSize a :: Word64
a) -> Word64
a) CSize
dataSize) Ptr ()
pData
instance Storable PipelineExecutableInternalRepresentationKHR where
sizeOf :: PipelineExecutableInternalRepresentationKHR -> Int
sizeOf ~PipelineExecutableInternalRepresentationKHR
_ = 552
alignment :: PipelineExecutableInternalRepresentationKHR -> Int
alignment ~PipelineExecutableInternalRepresentationKHR
_ = 8
peek :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO PipelineExecutableInternalRepresentationKHR
peek = ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> IO PipelineExecutableInternalRepresentationKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> PipelineExecutableInternalRepresentationKHR -> IO ()
poke ptr :: "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
ptr poked :: PipelineExecutableInternalRepresentationKHR
poked = ("pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR)
-> PipelineExecutableInternalRepresentationKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInternalRepresentations"
::: Ptr PipelineExecutableInternalRepresentationKHR
ptr PipelineExecutableInternalRepresentationKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineExecutableInternalRepresentationKHR where
zero :: PipelineExecutableInternalRepresentationKHR
zero = ByteString
-> ByteString
-> Bool
-> Word64
-> Ptr ()
-> PipelineExecutableInternalRepresentationKHR
PipelineExecutableInternalRepresentationKHR
ByteString
forall a. Monoid a => a
mempty
ByteString
forall a. Monoid a => a
mempty
Bool
forall a. Zero a => a
zero
Word64
forall a. Zero a => a
zero
Ptr ()
forall a. Zero a => a
zero
data PipelineExecutableStatisticValueKHR
= B32 Bool
| I64 Int64
| U64 Word64
| F64 Double
deriving (Int -> PipelineExecutableStatisticValueKHR -> ShowS
[PipelineExecutableStatisticValueKHR] -> ShowS
PipelineExecutableStatisticValueKHR -> String
(Int -> PipelineExecutableStatisticValueKHR -> ShowS)
-> (PipelineExecutableStatisticValueKHR -> String)
-> ([PipelineExecutableStatisticValueKHR] -> ShowS)
-> Show PipelineExecutableStatisticValueKHR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PipelineExecutableStatisticValueKHR] -> ShowS
$cshowList :: [PipelineExecutableStatisticValueKHR] -> ShowS
show :: PipelineExecutableStatisticValueKHR -> String
$cshow :: PipelineExecutableStatisticValueKHR -> String
showsPrec :: Int -> PipelineExecutableStatisticValueKHR -> ShowS
$cshowsPrec :: Int -> PipelineExecutableStatisticValueKHR -> ShowS
Show)
instance ToCStruct PipelineExecutableStatisticValueKHR where
withCStruct :: PipelineExecutableStatisticValueKHR
-> (Ptr PipelineExecutableStatisticValueKHR -> IO b) -> IO b
withCStruct x :: PipelineExecutableStatisticValueKHR
x f :: Ptr PipelineExecutableStatisticValueKHR -> IO b
f = Int
-> Int -> (Ptr PipelineExecutableStatisticValueKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 8 ((Ptr PipelineExecutableStatisticValueKHR -> IO b) -> IO b)
-> (Ptr PipelineExecutableStatisticValueKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineExecutableStatisticValueKHR
p -> Ptr PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticValueKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineExecutableStatisticValueKHR
p PipelineExecutableStatisticValueKHR
x (Ptr PipelineExecutableStatisticValueKHR -> IO b
f Ptr PipelineExecutableStatisticValueKHR
p)
pokeCStruct :: Ptr PipelineExecutableStatisticValueKHR -> PipelineExecutableStatisticValueKHR -> IO a -> IO a
pokeCStruct :: Ptr PipelineExecutableStatisticValueKHR
-> PipelineExecutableStatisticValueKHR -> IO a -> IO a
pokeCStruct p :: Ptr PipelineExecutableStatisticValueKHR
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (PipelineExecutableStatisticValueKHR -> (() -> IO a) -> IO a)
-> PipelineExecutableStatisticValueKHR
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (PipelineExecutableStatisticValueKHR -> ContT a IO ())
-> PipelineExecutableStatisticValueKHR
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
B32 v :: Bool
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineExecutableStatisticValueKHR -> Ptr Bool32
forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PipelineExecutableStatisticValueKHR
p) (Bool -> Bool32
boolToBool32 (Bool
v))
I64 v :: Int64
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Int64 -> Int64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineExecutableStatisticValueKHR -> Ptr Int64
forall a b. Ptr a -> Ptr b
castPtr @_ @Int64 Ptr PipelineExecutableStatisticValueKHR
p) (Int64
v)
U64 v :: Word64
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineExecutableStatisticValueKHR -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PipelineExecutableStatisticValueKHR
p) (Word64
v)
F64 v :: Double
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineExecutableStatisticValueKHR -> Ptr CDouble
forall a b. Ptr a -> Ptr b
castPtr @_ @CDouble Ptr PipelineExecutableStatisticValueKHR
p) (Double -> CDouble
CDouble (Double
v))
pokeZeroCStruct :: Ptr PipelineExecutableStatisticValueKHR -> IO b -> IO b
pokeZeroCStruct :: Ptr PipelineExecutableStatisticValueKHR -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
cStructSize :: Int
cStructSize = 8
cStructAlignment :: Int
cStructAlignment = 8
instance Zero PipelineExecutableStatisticValueKHR where
zero :: PipelineExecutableStatisticValueKHR
zero = Int64 -> PipelineExecutableStatisticValueKHR
I64 Int64
forall a. Zero a => a
zero
peekPipelineExecutableStatisticValueKHR :: PipelineExecutableStatisticFormatKHR -> Ptr PipelineExecutableStatisticValueKHR -> IO PipelineExecutableStatisticValueKHR
peekPipelineExecutableStatisticValueKHR :: PipelineExecutableStatisticFormatKHR
-> Ptr PipelineExecutableStatisticValueKHR
-> IO PipelineExecutableStatisticValueKHR
peekPipelineExecutableStatisticValueKHR tag :: PipelineExecutableStatisticFormatKHR
tag p :: Ptr PipelineExecutableStatisticValueKHR
p = case PipelineExecutableStatisticFormatKHR
tag of
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR -> Bool -> PipelineExecutableStatisticValueKHR
B32 (Bool -> PipelineExecutableStatisticValueKHR)
-> IO Bool -> IO PipelineExecutableStatisticValueKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Bool32
b32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (Ptr PipelineExecutableStatisticValueKHR -> Ptr Bool32
forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PipelineExecutableStatisticValueKHR
p)
Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
b32)
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR -> Int64 -> PipelineExecutableStatisticValueKHR
I64 (Int64 -> PipelineExecutableStatisticValueKHR)
-> IO Int64 -> IO PipelineExecutableStatisticValueKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek @Int64 (Ptr PipelineExecutableStatisticValueKHR -> Ptr Int64
forall a b. Ptr a -> Ptr b
castPtr @_ @Int64 Ptr PipelineExecutableStatisticValueKHR
p))
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR -> Word64 -> PipelineExecutableStatisticValueKHR
U64 (Word64 -> PipelineExecutableStatisticValueKHR)
-> IO Word64 -> IO PipelineExecutableStatisticValueKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 (Ptr PipelineExecutableStatisticValueKHR -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PipelineExecutableStatisticValueKHR
p))
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR -> Double -> PipelineExecutableStatisticValueKHR
F64 (Double -> PipelineExecutableStatisticValueKHR)
-> IO Double -> IO PipelineExecutableStatisticValueKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
CDouble
f64 <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek @CDouble (Ptr PipelineExecutableStatisticValueKHR -> Ptr CDouble
forall a b. Ptr a -> Ptr b
castPtr @_ @CDouble Ptr PipelineExecutableStatisticValueKHR
p)
Double -> IO Double
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double -> IO Double) -> Double -> IO Double
forall a b. (a -> b) -> a -> b
$ (\(CDouble a :: Double
a) -> Double
a) CDouble
f64)
newtype PipelineExecutableStatisticFormatKHR = PipelineExecutableStatisticFormatKHR Int32
deriving newtype (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
(PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> Eq PipelineExecutableStatisticFormatKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c/= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
== :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c== :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
Eq, Eq PipelineExecutableStatisticFormatKHR
Eq PipelineExecutableStatisticFormatKHR =>
(PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Ordering)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR)
-> (PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR)
-> Ord PipelineExecutableStatisticFormatKHR
PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Ordering
PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
$cmin :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
max :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
$cmax :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR
>= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c>= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
> :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c> :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
<= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c<= :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
< :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
$c< :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Bool
compare :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Ordering
$ccompare :: PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> Ordering
$cp1Ord :: Eq PipelineExecutableStatisticFormatKHR
Ord, Ptr b -> Int -> IO PipelineExecutableStatisticFormatKHR
Ptr b -> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
Ptr PipelineExecutableStatisticFormatKHR
-> IO PipelineExecutableStatisticFormatKHR
Ptr PipelineExecutableStatisticFormatKHR
-> Int -> IO PipelineExecutableStatisticFormatKHR
Ptr PipelineExecutableStatisticFormatKHR
-> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ()
PipelineExecutableStatisticFormatKHR -> Int
(PipelineExecutableStatisticFormatKHR -> Int)
-> (PipelineExecutableStatisticFormatKHR -> Int)
-> (Ptr PipelineExecutableStatisticFormatKHR
-> Int -> IO PipelineExecutableStatisticFormatKHR)
-> (Ptr PipelineExecutableStatisticFormatKHR
-> Int -> PipelineExecutableStatisticFormatKHR -> IO ())
-> (forall b.
Ptr b -> Int -> IO PipelineExecutableStatisticFormatKHR)
-> (forall b.
Ptr b -> Int -> PipelineExecutableStatisticFormatKHR -> IO ())
-> (Ptr PipelineExecutableStatisticFormatKHR
-> IO PipelineExecutableStatisticFormatKHR)
-> (Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ())
-> Storable PipelineExecutableStatisticFormatKHR
forall b. Ptr b -> Int -> IO PipelineExecutableStatisticFormatKHR
forall b.
Ptr b -> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ()
$cpoke :: Ptr PipelineExecutableStatisticFormatKHR
-> PipelineExecutableStatisticFormatKHR -> IO ()
peek :: Ptr PipelineExecutableStatisticFormatKHR
-> IO PipelineExecutableStatisticFormatKHR
$cpeek :: Ptr PipelineExecutableStatisticFormatKHR
-> IO PipelineExecutableStatisticFormatKHR
pokeByteOff :: Ptr b -> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO PipelineExecutableStatisticFormatKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PipelineExecutableStatisticFormatKHR
pokeElemOff :: Ptr PipelineExecutableStatisticFormatKHR
-> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
$cpokeElemOff :: Ptr PipelineExecutableStatisticFormatKHR
-> Int -> PipelineExecutableStatisticFormatKHR -> IO ()
peekElemOff :: Ptr PipelineExecutableStatisticFormatKHR
-> Int -> IO PipelineExecutableStatisticFormatKHR
$cpeekElemOff :: Ptr PipelineExecutableStatisticFormatKHR
-> Int -> IO PipelineExecutableStatisticFormatKHR
alignment :: PipelineExecutableStatisticFormatKHR -> Int
$calignment :: PipelineExecutableStatisticFormatKHR -> Int
sizeOf :: PipelineExecutableStatisticFormatKHR -> Int
$csizeOf :: PipelineExecutableStatisticFormatKHR -> Int
Storable, PipelineExecutableStatisticFormatKHR
PipelineExecutableStatisticFormatKHR
-> Zero PipelineExecutableStatisticFormatKHR
forall a. a -> Zero a
zero :: PipelineExecutableStatisticFormatKHR
$czero :: PipelineExecutableStatisticFormatKHR
Zero)
pattern $bPIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR :: PipelineExecutableStatisticFormatKHR
$mPIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR :: forall r.
PipelineExecutableStatisticFormatKHR
-> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR = PipelineExecutableStatisticFormatKHR 0
pattern $bPIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR :: PipelineExecutableStatisticFormatKHR
$mPIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR :: forall r.
PipelineExecutableStatisticFormatKHR
-> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR = PipelineExecutableStatisticFormatKHR 1
pattern $bPIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR :: PipelineExecutableStatisticFormatKHR
$mPIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR :: forall r.
PipelineExecutableStatisticFormatKHR
-> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR = PipelineExecutableStatisticFormatKHR 2
pattern $bPIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR :: PipelineExecutableStatisticFormatKHR
$mPIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR :: forall r.
PipelineExecutableStatisticFormatKHR
-> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR = PipelineExecutableStatisticFormatKHR 3
{-# complete PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR,
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR,
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR,
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR :: PipelineExecutableStatisticFormatKHR #-}
instance Show PipelineExecutableStatisticFormatKHR where
showsPrec :: Int -> PipelineExecutableStatisticFormatKHR -> ShowS
showsPrec p :: Int
p = \case
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR -> String -> ShowS
showString "PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR"
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR -> String -> ShowS
showString "PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR"
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR -> String -> ShowS
showString "PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR"
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR -> String -> ShowS
showString "PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR"
PipelineExecutableStatisticFormatKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PipelineExecutableStatisticFormatKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)
instance Read PipelineExecutableStatisticFormatKHR where
readPrec :: ReadPrec PipelineExecutableStatisticFormatKHR
readPrec = ReadPrec PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PipelineExecutableStatisticFormatKHR)]
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR", PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineExecutableStatisticFormatKHR
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_BOOL32_KHR)
, ("PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR", PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineExecutableStatisticFormatKHR
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_INT64_KHR)
, ("PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR", PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineExecutableStatisticFormatKHR
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_UINT64_KHR)
, ("PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR", PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineExecutableStatisticFormatKHR
PIPELINE_EXECUTABLE_STATISTIC_FORMAT_FLOAT64_KHR)]
ReadPrec PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PipelineExecutableStatisticFormatKHR")
Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
PipelineExecutableStatisticFormatKHR
-> ReadPrec PipelineExecutableStatisticFormatKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> PipelineExecutableStatisticFormatKHR
PipelineExecutableStatisticFormatKHR Int32
v)))
type KHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION = 1
pattern KHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION :: a
$mKHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PIPELINE_EXECUTABLE_PROPERTIES_SPEC_VERSION = 1
type KHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME = "VK_KHR_pipeline_executable_properties"
pattern KHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME :: a
$mKHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PIPELINE_EXECUTABLE_PROPERTIES_EXTENSION_NAME = "VK_KHR_pipeline_executable_properties"