{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_validation_cache ( createValidationCacheEXT
, withValidationCacheEXT
, destroyValidationCacheEXT
, getValidationCacheDataEXT
, mergeValidationCachesEXT
, ValidationCacheCreateInfoEXT(..)
, ShaderModuleValidationCacheCreateInfoEXT(..)
, ValidationCacheCreateFlagsEXT(..)
, ValidationCacheHeaderVersionEXT( VALIDATION_CACHE_HEADER_VERSION_ONE_EXT
, ..
)
, EXT_VALIDATION_CACHE_SPEC_VERSION
, pattern EXT_VALIDATION_CACHE_SPEC_VERSION
, EXT_VALIDATION_CACHE_EXTENSION_NAME
, pattern EXT_VALIDATION_CACHE_EXTENSION_NAME
, ValidationCacheEXT(..)
) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
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.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import Data.ByteString (packCStringLen)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CSize(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CSize)
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.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Word (Word64)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreateValidationCacheEXT))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyValidationCacheEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetValidationCacheDataEXT))
import Vulkan.Dynamic (DeviceCmds(pVkMergeValidationCachesEXT))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (ValidationCacheEXT)
import Vulkan.Extensions.Handles (ValidationCacheEXT(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SHADER_MODULE_VALIDATION_CACHE_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_VALIDATION_CACHE_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (ValidationCacheEXT(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateValidationCacheEXT
:: FunPtr (Ptr Device_T -> Ptr ValidationCacheCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr ValidationCacheEXT -> IO Result) -> Ptr Device_T -> Ptr ValidationCacheCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr ValidationCacheEXT -> IO Result
createValidationCacheEXT :: forall io
. (MonadIO io)
=>
Device
->
ValidationCacheCreateInfoEXT
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (ValidationCacheEXT)
createValidationCacheEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ValidationCacheCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ValidationCacheEXT
createValidationCacheEXT Device
device ValidationCacheCreateInfoEXT
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkCreateValidationCacheEXTPtr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkCreateValidationCacheEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
pVkCreateValidationCacheEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkCreateValidationCacheEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreateValidationCacheEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCreateValidationCacheEXT' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
vkCreateValidationCacheEXT' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
mkVkCreateValidationCacheEXT FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkCreateValidationCacheEXTPtr
"pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ValidationCacheCreateInfoEXT
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pValidationCache" ::: Ptr ValidationCacheEXT
pPValidationCache <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @ValidationCacheEXT Int
8) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateValidationCacheEXT" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
vkCreateValidationCacheEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
pCreateInfo
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator
("pValidationCache" ::: Ptr ValidationCacheEXT
pPValidationCache))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
ValidationCacheEXT
pValidationCache <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @ValidationCacheEXT "pValidationCache" ::: Ptr ValidationCacheEXT
pPValidationCache
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (ValidationCacheEXT
pValidationCache)
withValidationCacheEXT :: forall io r . MonadIO io => Device -> ValidationCacheCreateInfoEXT -> Maybe AllocationCallbacks -> (io ValidationCacheEXT -> (ValidationCacheEXT -> io ()) -> r) -> r
withValidationCacheEXT :: forall (io :: * -> *) r.
MonadIO io =>
Device
-> ValidationCacheCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io ValidationCacheEXT -> (ValidationCacheEXT -> io ()) -> r)
-> r
withValidationCacheEXT Device
device ValidationCacheCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io ValidationCacheEXT -> (ValidationCacheEXT -> io ()) -> r
b =
io ValidationCacheEXT -> (ValidationCacheEXT -> io ()) -> r
b (forall (io :: * -> *).
MonadIO io =>
Device
-> ValidationCacheCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ValidationCacheEXT
createValidationCacheEXT Device
device ValidationCacheCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(ValidationCacheEXT
o0) -> forall (io :: * -> *).
MonadIO io =>
Device
-> ValidationCacheEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyValidationCacheEXT Device
device ValidationCacheEXT
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkDestroyValidationCacheEXT
:: FunPtr (Ptr Device_T -> ValidationCacheEXT -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> ValidationCacheEXT -> Ptr AllocationCallbacks -> IO ()
destroyValidationCacheEXT :: forall io
. (MonadIO io)
=>
Device
->
ValidationCacheEXT
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyValidationCacheEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ValidationCacheEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyValidationCacheEXT Device
device
ValidationCacheEXT
validationCache
"allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkDestroyValidationCacheEXTPtr :: FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyValidationCacheEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkDestroyValidationCacheEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyValidationCacheEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDestroyValidationCacheEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkDestroyValidationCacheEXT' :: Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyValidationCacheEXT' = FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyValidationCacheEXT FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyValidationCacheEXTPtr
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyValidationCacheEXT" (Ptr Device_T
-> ValidationCacheEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyValidationCacheEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ValidationCacheEXT
validationCache)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetValidationCacheDataEXT
:: FunPtr (Ptr Device_T -> ValidationCacheEXT -> Ptr CSize -> Ptr () -> IO Result) -> Ptr Device_T -> ValidationCacheEXT -> Ptr CSize -> Ptr () -> IO Result
getValidationCacheDataEXT :: forall io
. (MonadIO io)
=>
Device
->
ValidationCacheEXT
-> io (Result, ("data" ::: ByteString))
getValidationCacheDataEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> ValidationCacheEXT -> io (Result, "data" ::: ByteString)
getValidationCacheDataEXT Device
device ValidationCacheEXT
validationCache = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetValidationCacheDataEXTPtr :: FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
vkGetValidationCacheDataEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
pVkGetValidationCacheDataEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
vkGetValidationCacheDataEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetValidationCacheDataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetValidationCacheDataEXT' :: Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetValidationCacheDataEXT' = FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
-> Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
mkVkGetValidationCacheDataEXT FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
vkGetValidationCacheDataEXTPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pDataSize" ::: Ptr CSize
pPDataSize <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @CSize Int
8) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetValidationCacheDataEXT" (Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetValidationCacheDataEXT'
Ptr Device_T
device'
(ValidationCacheEXT
validationCache)
("pDataSize" ::: Ptr CSize
pPDataSize)
(forall a. Ptr a
nullPtr))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
CSize
pDataSize <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
"pData" ::: Ptr ()
pPData <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @(()) (forall a b. (Integral a, Num b) => a -> b
fromIntegral ((coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
pDataSize)))) forall a. Ptr a -> IO ()
free
Result
r' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetValidationCacheDataEXT" (Ptr Device_T
-> ValidationCacheEXT
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetValidationCacheDataEXT'
Ptr Device_T
device'
(ValidationCacheEXT
validationCache)
("pDataSize" ::: Ptr CSize
pPDataSize)
("pData" ::: Ptr ()
pPData))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
CSize
pDataSize'' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
"data" ::: ByteString
pData' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ CStringLen -> IO ("data" ::: ByteString)
packCStringLen ( forall a b. Ptr a -> Ptr b
castPtr @() @CChar "pData" ::: Ptr ()
pPData
, (forall a b. (Integral a, Num b) => a -> b
fromIntegral ((coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
pDataSize''))) )
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ((Result
r'), "data" ::: ByteString
pData')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkMergeValidationCachesEXT
:: FunPtr (Ptr Device_T -> ValidationCacheEXT -> Word32 -> Ptr ValidationCacheEXT -> IO Result) -> Ptr Device_T -> ValidationCacheEXT -> Word32 -> Ptr ValidationCacheEXT -> IO Result
mergeValidationCachesEXT :: forall io
. (MonadIO io)
=>
Device
->
("dstCache" ::: ValidationCacheEXT)
->
("srcCaches" ::: Vector ValidationCacheEXT)
-> io ()
mergeValidationCachesEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ValidationCacheEXT
-> ("srcCaches" ::: Vector ValidationCacheEXT)
-> io ()
mergeValidationCachesEXT Device
device ValidationCacheEXT
dstCache "srcCaches" ::: Vector ValidationCacheEXT
srcCaches = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkMergeValidationCachesEXTPtr :: FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkMergeValidationCachesEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
pVkMergeValidationCachesEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkMergeValidationCachesEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkMergeValidationCachesEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkMergeValidationCachesEXT' :: Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
vkMergeValidationCachesEXT' = FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
-> Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
mkVkMergeValidationCachesEXT FunPtr
(Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result)
vkMergeValidationCachesEXTPtr
"pValidationCache" ::: Ptr ValidationCacheEXT
pPSrcCaches <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @ValidationCacheEXT ((forall a. Vector a -> Int
Data.Vector.length ("srcCaches" ::: Vector ValidationCacheEXT
srcCaches)) forall a. Num a => a -> a -> a
* Int
8)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ValidationCacheEXT
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pValidationCache" ::: Ptr ValidationCacheEXT
pPSrcCaches forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ValidationCacheEXT) (ValidationCacheEXT
e)) ("srcCaches" ::: Vector ValidationCacheEXT
srcCaches)
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkMergeValidationCachesEXT" (Ptr Device_T
-> ValidationCacheEXT
-> ("srcCacheCount" ::: Word32)
-> ("pValidationCache" ::: Ptr ValidationCacheEXT)
-> IO Result
vkMergeValidationCachesEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ValidationCacheEXT
dstCache)
((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("srcCaches" ::: Vector ValidationCacheEXT
srcCaches)) :: Word32))
("pValidationCache" ::: Ptr ValidationCacheEXT
pPSrcCaches))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data ValidationCacheCreateInfoEXT = ValidationCacheCreateInfoEXT
{
ValidationCacheCreateInfoEXT -> ValidationCacheCreateFlagsEXT
flags :: ValidationCacheCreateFlagsEXT
,
ValidationCacheCreateInfoEXT -> Word64
initialDataSize :: Word64
,
ValidationCacheCreateInfoEXT -> "pData" ::: Ptr ()
initialData :: Ptr ()
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ValidationCacheCreateInfoEXT)
#endif
deriving instance Show ValidationCacheCreateInfoEXT
instance ToCStruct ValidationCacheCreateInfoEXT where
withCStruct :: forall b.
ValidationCacheCreateInfoEXT
-> (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT) -> IO b)
-> IO b
withCStruct ValidationCacheCreateInfoEXT
x ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p ValidationCacheCreateInfoEXT
x (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT) -> IO b
f "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p)
pokeCStruct :: forall b.
("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ValidationCacheCreateInfoEXT -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p ValidationCacheCreateInfoEXT{Word64
"pData" ::: Ptr ()
ValidationCacheCreateFlagsEXT
initialData :: "pData" ::: Ptr ()
initialDataSize :: Word64
flags :: ValidationCacheCreateFlagsEXT
$sel:initialData:ValidationCacheCreateInfoEXT :: ValidationCacheCreateInfoEXT -> "pData" ::: Ptr ()
$sel:initialDataSize:ValidationCacheCreateInfoEXT :: ValidationCacheCreateInfoEXT -> Word64
$sel:flags:ValidationCacheCreateInfoEXT :: ValidationCacheCreateInfoEXT -> ValidationCacheCreateFlagsEXT
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_VALIDATION_CACHE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ValidationCacheCreateFlagsEXT)) (ValidationCacheCreateFlagsEXT
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
initialDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
initialData)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_VALIDATION_CACHE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ValidationCacheCreateInfoEXT where
peekCStruct :: ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> IO ValidationCacheCreateInfoEXT
peekCStruct "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p = do
ValidationCacheCreateFlagsEXT
flags <- forall a. Storable a => Ptr a -> IO a
peek @ValidationCacheCreateFlagsEXT (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ValidationCacheCreateFlagsEXT))
CSize
initialDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize))
"pData" ::: Ptr ()
pInitialData <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ValidationCacheCreateFlagsEXT
-> Word64 -> ("pData" ::: Ptr ()) -> ValidationCacheCreateInfoEXT
ValidationCacheCreateInfoEXT
ValidationCacheCreateFlagsEXT
flags (coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
initialDataSize) "pData" ::: Ptr ()
pInitialData
instance Storable ValidationCacheCreateInfoEXT where
sizeOf :: ValidationCacheCreateInfoEXT -> Int
sizeOf ~ValidationCacheCreateInfoEXT
_ = Int
40
alignment :: ValidationCacheCreateInfoEXT -> Int
alignment ~ValidationCacheCreateInfoEXT
_ = Int
8
peek :: ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> IO ValidationCacheCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT)
-> ValidationCacheCreateInfoEXT -> IO ()
poke "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
ptr ValidationCacheCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr ValidationCacheCreateInfoEXT
ptr ValidationCacheCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ValidationCacheCreateInfoEXT where
zero :: ValidationCacheCreateInfoEXT
zero = ValidationCacheCreateFlagsEXT
-> Word64 -> ("pData" ::: Ptr ()) -> ValidationCacheCreateInfoEXT
ValidationCacheCreateInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data ShaderModuleValidationCacheCreateInfoEXT = ShaderModuleValidationCacheCreateInfoEXT
{
ShaderModuleValidationCacheCreateInfoEXT -> ValidationCacheEXT
validationCache :: ValidationCacheEXT }
deriving (Typeable, ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> Bool
$c/= :: ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> Bool
== :: ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> Bool
$c== :: ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ShaderModuleValidationCacheCreateInfoEXT)
#endif
deriving instance Show ShaderModuleValidationCacheCreateInfoEXT
instance ToCStruct ShaderModuleValidationCacheCreateInfoEXT where
withCStruct :: forall b.
ShaderModuleValidationCacheCreateInfoEXT
-> (Ptr ShaderModuleValidationCacheCreateInfoEXT -> IO b) -> IO b
withCStruct ShaderModuleValidationCacheCreateInfoEXT
x Ptr ShaderModuleValidationCacheCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ShaderModuleValidationCacheCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ShaderModuleValidationCacheCreateInfoEXT
p ShaderModuleValidationCacheCreateInfoEXT
x (Ptr ShaderModuleValidationCacheCreateInfoEXT -> IO b
f Ptr ShaderModuleValidationCacheCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr ShaderModuleValidationCacheCreateInfoEXT
p ShaderModuleValidationCacheCreateInfoEXT{ValidationCacheEXT
validationCache :: ValidationCacheEXT
$sel:validationCache:ShaderModuleValidationCacheCreateInfoEXT :: ShaderModuleValidationCacheCreateInfoEXT -> ValidationCacheEXT
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SHADER_MODULE_VALIDATION_CACHE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ValidationCacheEXT)) (ValidationCacheEXT
validationCache)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr ShaderModuleValidationCacheCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr ShaderModuleValidationCacheCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SHADER_MODULE_VALIDATION_CACHE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ValidationCacheEXT)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ShaderModuleValidationCacheCreateInfoEXT where
peekCStruct :: Ptr ShaderModuleValidationCacheCreateInfoEXT
-> IO ShaderModuleValidationCacheCreateInfoEXT
peekCStruct Ptr ShaderModuleValidationCacheCreateInfoEXT
p = do
ValidationCacheEXT
validationCache <- forall a. Storable a => Ptr a -> IO a
peek @ValidationCacheEXT ((Ptr ShaderModuleValidationCacheCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ValidationCacheEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ValidationCacheEXT -> ShaderModuleValidationCacheCreateInfoEXT
ShaderModuleValidationCacheCreateInfoEXT
ValidationCacheEXT
validationCache
instance Storable ShaderModuleValidationCacheCreateInfoEXT where
sizeOf :: ShaderModuleValidationCacheCreateInfoEXT -> Int
sizeOf ~ShaderModuleValidationCacheCreateInfoEXT
_ = Int
24
alignment :: ShaderModuleValidationCacheCreateInfoEXT -> Int
alignment ~ShaderModuleValidationCacheCreateInfoEXT
_ = Int
8
peek :: Ptr ShaderModuleValidationCacheCreateInfoEXT
-> IO ShaderModuleValidationCacheCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ShaderModuleValidationCacheCreateInfoEXT
-> ShaderModuleValidationCacheCreateInfoEXT -> IO ()
poke Ptr ShaderModuleValidationCacheCreateInfoEXT
ptr ShaderModuleValidationCacheCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ShaderModuleValidationCacheCreateInfoEXT
ptr ShaderModuleValidationCacheCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ShaderModuleValidationCacheCreateInfoEXT where
zero :: ShaderModuleValidationCacheCreateInfoEXT
zero = ValidationCacheEXT -> ShaderModuleValidationCacheCreateInfoEXT
ShaderModuleValidationCacheCreateInfoEXT
forall a. Zero a => a
zero
newtype ValidationCacheCreateFlagsEXT = ValidationCacheCreateFlagsEXT Flags
deriving newtype (ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c/= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
== :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c== :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
Eq, Eq ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Ordering
ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
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 :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$cmin :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
max :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$cmax :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
>= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c>= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
> :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c> :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
<= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c<= :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
< :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
$c< :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Bool
compare :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Ordering
$ccompare :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> Ordering
Ord, Ptr ValidationCacheCreateFlagsEXT
-> IO ValidationCacheCreateFlagsEXT
Ptr ValidationCacheCreateFlagsEXT
-> Int -> IO ValidationCacheCreateFlagsEXT
Ptr ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT -> IO ()
Ptr ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> IO ()
ValidationCacheCreateFlagsEXT -> Int
forall b. Ptr b -> Int -> IO ValidationCacheCreateFlagsEXT
forall b. Ptr b -> Int -> ValidationCacheCreateFlagsEXT -> 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 ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> IO ()
$cpoke :: Ptr ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> IO ()
peek :: Ptr ValidationCacheCreateFlagsEXT
-> IO ValidationCacheCreateFlagsEXT
$cpeek :: Ptr ValidationCacheCreateFlagsEXT
-> IO ValidationCacheCreateFlagsEXT
pokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheCreateFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheCreateFlagsEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheCreateFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheCreateFlagsEXT
pokeElemOff :: Ptr ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT -> IO ()
$cpokeElemOff :: Ptr ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT -> IO ()
peekElemOff :: Ptr ValidationCacheCreateFlagsEXT
-> Int -> IO ValidationCacheCreateFlagsEXT
$cpeekElemOff :: Ptr ValidationCacheCreateFlagsEXT
-> Int -> IO ValidationCacheCreateFlagsEXT
alignment :: ValidationCacheCreateFlagsEXT -> Int
$calignment :: ValidationCacheCreateFlagsEXT -> Int
sizeOf :: ValidationCacheCreateFlagsEXT -> Int
$csizeOf :: ValidationCacheCreateFlagsEXT -> Int
Storable, ValidationCacheCreateFlagsEXT
forall a. a -> Zero a
zero :: ValidationCacheCreateFlagsEXT
$czero :: ValidationCacheCreateFlagsEXT
Zero, Eq ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT
Int -> ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT -> Bool
ValidationCacheCreateFlagsEXT -> Int
ValidationCacheCreateFlagsEXT -> Maybe Int
ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT -> Int -> Bool
ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: ValidationCacheCreateFlagsEXT -> Int
$cpopCount :: ValidationCacheCreateFlagsEXT -> Int
rotateR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$crotateR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
rotateL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$crotateL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
unsafeShiftR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cunsafeShiftR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
shiftR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cshiftR :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
unsafeShiftL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cunsafeShiftL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
shiftL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cshiftL :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
isSigned :: ValidationCacheCreateFlagsEXT -> Bool
$cisSigned :: ValidationCacheCreateFlagsEXT -> Bool
bitSize :: ValidationCacheCreateFlagsEXT -> Int
$cbitSize :: ValidationCacheCreateFlagsEXT -> Int
bitSizeMaybe :: ValidationCacheCreateFlagsEXT -> Maybe Int
$cbitSizeMaybe :: ValidationCacheCreateFlagsEXT -> Maybe Int
testBit :: ValidationCacheCreateFlagsEXT -> Int -> Bool
$ctestBit :: ValidationCacheCreateFlagsEXT -> Int -> Bool
complementBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$ccomplementBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
clearBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cclearBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
setBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$csetBit :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
bit :: Int -> ValidationCacheCreateFlagsEXT
$cbit :: Int -> ValidationCacheCreateFlagsEXT
zeroBits :: ValidationCacheCreateFlagsEXT
$czeroBits :: ValidationCacheCreateFlagsEXT
rotate :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$crotate :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
shift :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
$cshift :: ValidationCacheCreateFlagsEXT
-> Int -> ValidationCacheCreateFlagsEXT
complement :: ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$ccomplement :: ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
xor :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$cxor :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
.|. :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$c.|. :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
.&. :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
$c.&. :: ValidationCacheCreateFlagsEXT
-> ValidationCacheCreateFlagsEXT -> ValidationCacheCreateFlagsEXT
Bits, Bits ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: ValidationCacheCreateFlagsEXT -> Int
$ccountTrailingZeros :: ValidationCacheCreateFlagsEXT -> Int
countLeadingZeros :: ValidationCacheCreateFlagsEXT -> Int
$ccountLeadingZeros :: ValidationCacheCreateFlagsEXT -> Int
finiteBitSize :: ValidationCacheCreateFlagsEXT -> Int
$cfiniteBitSize :: ValidationCacheCreateFlagsEXT -> Int
FiniteBits)
conNameValidationCacheCreateFlagsEXT :: String
conNameValidationCacheCreateFlagsEXT :: String
conNameValidationCacheCreateFlagsEXT = String
"ValidationCacheCreateFlagsEXT"
enumPrefixValidationCacheCreateFlagsEXT :: String
enumPrefixValidationCacheCreateFlagsEXT :: String
enumPrefixValidationCacheCreateFlagsEXT = String
""
showTableValidationCacheCreateFlagsEXT :: [(ValidationCacheCreateFlagsEXT, String)]
showTableValidationCacheCreateFlagsEXT :: [(ValidationCacheCreateFlagsEXT, String)]
showTableValidationCacheCreateFlagsEXT = []
instance Show ValidationCacheCreateFlagsEXT where
showsPrec :: Int -> ValidationCacheCreateFlagsEXT -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixValidationCacheCreateFlagsEXT
[(ValidationCacheCreateFlagsEXT, String)]
showTableValidationCacheCreateFlagsEXT
String
conNameValidationCacheCreateFlagsEXT
(\(ValidationCacheCreateFlagsEXT "srcCacheCount" ::: Word32
x) -> "srcCacheCount" ::: Word32
x)
(\"srcCacheCount" ::: Word32
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex "srcCacheCount" ::: Word32
x)
instance Read ValidationCacheCreateFlagsEXT where
readPrec :: ReadPrec ValidationCacheCreateFlagsEXT
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixValidationCacheCreateFlagsEXT
[(ValidationCacheCreateFlagsEXT, String)]
showTableValidationCacheCreateFlagsEXT
String
conNameValidationCacheCreateFlagsEXT
("srcCacheCount" ::: Word32) -> ValidationCacheCreateFlagsEXT
ValidationCacheCreateFlagsEXT
newtype = Int32
deriving newtype (ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c/= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
== :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c== :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
Eq, Eq ValidationCacheHeaderVersionEXT
ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Ordering
ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
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 :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
$cmin :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
max :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
$cmax :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT
>= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c>= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
> :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c> :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
<= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c<= :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
< :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
$c< :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Bool
compare :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Ordering
$ccompare :: ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> Ordering
Ord, Ptr ValidationCacheHeaderVersionEXT
-> IO ValidationCacheHeaderVersionEXT
Ptr ValidationCacheHeaderVersionEXT
-> Int -> IO ValidationCacheHeaderVersionEXT
Ptr ValidationCacheHeaderVersionEXT
-> Int -> ValidationCacheHeaderVersionEXT -> IO ()
Ptr ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> IO ()
ValidationCacheHeaderVersionEXT -> Int
forall b. Ptr b -> Int -> IO ValidationCacheHeaderVersionEXT
forall b. Ptr b -> Int -> ValidationCacheHeaderVersionEXT -> 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 ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> IO ()
$cpoke :: Ptr ValidationCacheHeaderVersionEXT
-> ValidationCacheHeaderVersionEXT -> IO ()
peek :: Ptr ValidationCacheHeaderVersionEXT
-> IO ValidationCacheHeaderVersionEXT
$cpeek :: Ptr ValidationCacheHeaderVersionEXT
-> IO ValidationCacheHeaderVersionEXT
pokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheHeaderVersionEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheHeaderVersionEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheHeaderVersionEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheHeaderVersionEXT
pokeElemOff :: Ptr ValidationCacheHeaderVersionEXT
-> Int -> ValidationCacheHeaderVersionEXT -> IO ()
$cpokeElemOff :: Ptr ValidationCacheHeaderVersionEXT
-> Int -> ValidationCacheHeaderVersionEXT -> IO ()
peekElemOff :: Ptr ValidationCacheHeaderVersionEXT
-> Int -> IO ValidationCacheHeaderVersionEXT
$cpeekElemOff :: Ptr ValidationCacheHeaderVersionEXT
-> Int -> IO ValidationCacheHeaderVersionEXT
alignment :: ValidationCacheHeaderVersionEXT -> Int
$calignment :: ValidationCacheHeaderVersionEXT -> Int
sizeOf :: ValidationCacheHeaderVersionEXT -> Int
$csizeOf :: ValidationCacheHeaderVersionEXT -> Int
Storable, ValidationCacheHeaderVersionEXT
forall a. a -> Zero a
zero :: ValidationCacheHeaderVersionEXT
$czero :: ValidationCacheHeaderVersionEXT
Zero)
pattern = ValidationCacheHeaderVersionEXT 1
{-# COMPLETE VALIDATION_CACHE_HEADER_VERSION_ONE_EXT :: ValidationCacheHeaderVersionEXT #-}
conNameValidationCacheHeaderVersionEXT :: String
= String
"ValidationCacheHeaderVersionEXT"
enumPrefixValidationCacheHeaderVersionEXT :: String
= String
"VALIDATION_CACHE_HEADER_VERSION_ONE_EXT"
showTableValidationCacheHeaderVersionEXT :: [(ValidationCacheHeaderVersionEXT, String)]
=
[
( ValidationCacheHeaderVersionEXT
VALIDATION_CACHE_HEADER_VERSION_ONE_EXT
, String
""
)
]
instance Show ValidationCacheHeaderVersionEXT where
showsPrec :: Int -> ValidationCacheHeaderVersionEXT -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixValidationCacheHeaderVersionEXT
[(ValidationCacheHeaderVersionEXT, String)]
showTableValidationCacheHeaderVersionEXT
String
conNameValidationCacheHeaderVersionEXT
(\(ValidationCacheHeaderVersionEXT Int32
x) -> Int32
x)
(forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read ValidationCacheHeaderVersionEXT where
readPrec :: ReadPrec ValidationCacheHeaderVersionEXT
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixValidationCacheHeaderVersionEXT
[(ValidationCacheHeaderVersionEXT, String)]
showTableValidationCacheHeaderVersionEXT
String
conNameValidationCacheHeaderVersionEXT
Int32 -> ValidationCacheHeaderVersionEXT
ValidationCacheHeaderVersionEXT
type EXT_VALIDATION_CACHE_SPEC_VERSION = 1
pattern EXT_VALIDATION_CACHE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_VALIDATION_CACHE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_VALIDATION_CACHE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_VALIDATION_CACHE_SPEC_VERSION = 1
type EXT_VALIDATION_CACHE_EXTENSION_NAME = "VK_EXT_validation_cache"
pattern EXT_VALIDATION_CACHE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_VALIDATION_CACHE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_VALIDATION_CACHE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_VALIDATION_CACHE_EXTENSION_NAME = "VK_EXT_validation_cache"