{-# language CPP #-}
module Vulkan.Core10.DeviceInitialization  ( createInstance
                                           , withInstance
                                           , destroyInstance
                                           , enumeratePhysicalDevices
                                           , getDeviceProcAddr
                                           , getInstanceProcAddr
                                           , getPhysicalDeviceProperties
                                           , getPhysicalDeviceQueueFamilyProperties
                                           , getPhysicalDeviceMemoryProperties
                                           , getPhysicalDeviceFeatures
                                           , getPhysicalDeviceFormatProperties
                                           , getPhysicalDeviceImageFormatProperties
                                           , PhysicalDeviceProperties(..)
                                           , ApplicationInfo(..)
                                           , InstanceCreateInfo(..)
                                           , QueueFamilyProperties(..)
                                           , PhysicalDeviceMemoryProperties(..)
                                           , MemoryType(..)
                                           , MemoryHeap(..)
                                           , FormatProperties(..)
                                           , ImageFormatProperties(..)
                                           , PhysicalDeviceFeatures(..)
                                           , PhysicalDeviceSparseProperties(..)
                                           , PhysicalDeviceLimits(..)
                                           , Instance(..)
                                           , PhysicalDevice(..)
                                           , AllocationCallbacks(..)
                                           , InstanceCreateFlags(..)
                                           , ImageType(..)
                                           , ImageTiling(..)
                                           , InternalAllocationType(..)
                                           , SystemAllocationScope(..)
                                           , PhysicalDeviceType(..)
                                           , Format(..)
                                           , StructureType(..)
                                           , QueueFlagBits(..)
                                           , QueueFlags
                                           , MemoryPropertyFlagBits(..)
                                           , MemoryPropertyFlags
                                           , MemoryHeapFlagBits(..)
                                           , MemoryHeapFlags
                                           , ImageUsageFlagBits(..)
                                           , ImageUsageFlags
                                           , ImageCreateFlagBits(..)
                                           , ImageCreateFlags
                                           , FormatFeatureFlagBits(..)
                                           , FormatFeatureFlags
                                           , SampleCountFlagBits(..)
                                           , SampleCountFlags
                                           , FN_vkInternalAllocationNotification
                                           , PFN_vkInternalAllocationNotification
                                           , FN_vkInternalFreeNotification
                                           , PFN_vkInternalFreeNotification
                                           , FN_vkReallocationFunction
                                           , PFN_vkReallocationFunction
                                           , FN_vkAllocationFunction
                                           , PFN_vkAllocationFunction
                                           , FN_vkFreeFunction
                                           , PFN_vkFreeFunction
                                           , FN_vkVoidFunction
                                           , PFN_vkVoidFunction
                                           ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Utils (maybePeek)
import GHC.Base (when)
import GHC.IO (throwIO)
import Foreign.Ptr (castFunPtr)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CChar(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
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.Ptr (Ptr(Ptr))
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Word (Word8)
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.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.Dynamic (getInstanceProcAddr')
import Vulkan.Dynamic (initInstanceCmds)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Utils (peekByteStringFromSizedVectorPtr)
import Vulkan.CStruct.Utils (pokeFixedLengthByteString)
import Vulkan.CStruct.Utils (pokeFixedLengthNullTerminatedByteString)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_debug_report (DebugReportCallbackCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_debug_utils (DebugUtilsMessengerCreateInfoEXT)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceProcAddr))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.FundamentalTypes (Extent3D)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.Format (Format(..))
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlagBits(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling(..))
import Vulkan.Core10.Enums.ImageType (ImageType)
import Vulkan.Core10.Enums.ImageType (ImageType(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlagBits(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (Instance(Instance))
import Vulkan.Dynamic (InstanceCmds(pVkDestroyInstance))
import Vulkan.Dynamic (InstanceCmds(pVkEnumeratePhysicalDevices))
import Vulkan.Dynamic (InstanceCmds(pVkGetInstanceProcAddr))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceFeatures))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceFormatProperties))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceImageFormatProperties))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceMemoryProperties))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceProperties))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceQueueFamilyProperties))
import Vulkan.Core10.Enums.InstanceCreateFlags (InstanceCreateFlags)
import Vulkan.Core10.Handles (Instance_T)
import Vulkan.Core10.APIConstants (MAX_MEMORY_HEAPS)
import Vulkan.Core10.APIConstants (MAX_MEMORY_TYPES)
import Vulkan.Core10.APIConstants (MAX_PHYSICAL_DEVICE_NAME_SIZE)
import Vulkan.Core10.Enums.MemoryHeapFlagBits (MemoryHeapFlags)
import Vulkan.Core10.Enums.MemoryPropertyFlagBits (MemoryPropertyFlags)
import Vulkan.Core10.FuncPointers (PFN_vkVoidFunction)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(PhysicalDevice))
import Vulkan.Core10.Enums.PhysicalDeviceType (PhysicalDeviceType)
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.QueueFlagBits (QueueFlags)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.APIConstants (UUID_SIZE)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_validation_features (ValidationFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_validation_flags (ValidationFlagsEXT)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.APIConstants (pattern MAX_MEMORY_HEAPS)
import Vulkan.Core10.APIConstants (pattern MAX_MEMORY_TYPES)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_APPLICATION_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_INSTANCE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks(..))
import Vulkan.Core10.FuncPointers (FN_vkAllocationFunction)
import Vulkan.Core10.FuncPointers (FN_vkFreeFunction)
import Vulkan.Core10.FuncPointers (FN_vkInternalAllocationNotification)
import Vulkan.Core10.FuncPointers (FN_vkInternalFreeNotification)
import Vulkan.Core10.FuncPointers (FN_vkReallocationFunction)
import Vulkan.Core10.FuncPointers (FN_vkVoidFunction)
import Vulkan.Core10.Enums.Format (Format(..))
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlagBits(..))
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlagBits(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling(..))
import Vulkan.Core10.Enums.ImageType (ImageType(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlagBits(..))
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Enums.InstanceCreateFlags (InstanceCreateFlags(..))
import Vulkan.Core10.Enums.InternalAllocationType (InternalAllocationType(..))
import Vulkan.Core10.Enums.MemoryHeapFlagBits (MemoryHeapFlagBits(..))
import Vulkan.Core10.Enums.MemoryHeapFlagBits (MemoryHeapFlags)
import Vulkan.Core10.Enums.MemoryPropertyFlagBits (MemoryPropertyFlagBits(..))
import Vulkan.Core10.Enums.MemoryPropertyFlagBits (MemoryPropertyFlags)
import Vulkan.Core10.FuncPointers (PFN_vkAllocationFunction)
import Vulkan.Core10.FuncPointers (PFN_vkFreeFunction)
import Vulkan.Core10.FuncPointers (PFN_vkInternalAllocationNotification)
import Vulkan.Core10.FuncPointers (PFN_vkInternalFreeNotification)
import Vulkan.Core10.FuncPointers (PFN_vkReallocationFunction)
import Vulkan.Core10.FuncPointers (PFN_vkVoidFunction)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Enums.PhysicalDeviceType (PhysicalDeviceType(..))
import Vulkan.Core10.Enums.QueueFlagBits (QueueFlagBits(..))
import Vulkan.Core10.Enums.QueueFlagBits (QueueFlags)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
import Vulkan.Core10.Enums.SystemAllocationScope (SystemAllocationScope(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateInstance
  :: FunPtr (Ptr (SomeStruct InstanceCreateInfo) -> Ptr AllocationCallbacks -> Ptr (Ptr Instance_T) -> IO Result) -> Ptr (SomeStruct InstanceCreateInfo) -> Ptr AllocationCallbacks -> Ptr (Ptr Instance_T) -> IO Result

-- | vkCreateInstance - Create a new Vulkan instance
--
-- = Description
--
-- 'createInstance' verifies that the requested layers exist. If not,
-- 'createInstance' will return
-- 'Vulkan.Core10.Enums.Result.ERROR_LAYER_NOT_PRESENT'. Next
-- 'createInstance' verifies that the requested extensions are supported
-- (e.g. in the implementation or in any enabled instance layer) and if any
-- requested extension is not supported, 'createInstance' /must/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_EXTENSION_NOT_PRESENT'. After
-- verifying and enabling the instance layers and extensions the
-- 'Vulkan.Core10.Handles.Instance' object is created and returned to the
-- application. If a requested extension is only supported by a layer, both
-- the layer and the extension need to be specified at 'createInstance'
-- time for the creation to succeed.
--
-- == Valid Usage
--
-- -   All
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-extensions-extensiondependencies required extensions>
--     for each extension in the
--     'InstanceCreateInfo'::@ppEnabledExtensionNames@ list /must/ also be
--     present in that list
--
-- == Valid Usage (Implicit)
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'InstanceCreateInfo' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pInstance@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.Instance' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INITIALIZATION_FAILED'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_LAYER_NOT_PRESENT'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_EXTENSION_NOT_PRESENT'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INCOMPATIBLE_DRIVER'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Instance', 'InstanceCreateInfo'
createInstance :: forall a io
                . (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io)
               => -- | @pCreateInfo@ is a pointer to a 'InstanceCreateInfo' structure
                  -- controlling creation of the instance.
                  (InstanceCreateInfo a)
               -> -- | @pAllocator@ controls host memory allocation as described in the
                  -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                  -- chapter.
                  ("allocator" ::: Maybe AllocationCallbacks)
               -> io (Instance)
createInstance :: InstanceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance
createInstance createInfo :: InstanceCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Instance -> io Instance
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Instance -> io Instance)
-> (ContT Instance IO Instance -> IO Instance)
-> ContT Instance IO Instance
-> io Instance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Instance IO Instance -> IO Instance
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Instance IO Instance -> io Instance)
-> ContT Instance IO Instance -> io Instance
forall a b. (a -> b) -> a -> b
$ do
  FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> IO Result)
vkCreateInstancePtr <- IO
  (FunPtr
     (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pInstance" ::: Ptr (Ptr Instance_T))
      -> IO Result))
-> ContT
     Instance
     IO
     (FunPtr
        (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
         -> ("pAllocator" ::: Ptr AllocationCallbacks)
         -> ("pInstance" ::: Ptr (Ptr Instance_T))
         -> IO Result))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO
   (FunPtr
      (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
       -> ("pAllocator" ::: Ptr AllocationCallbacks)
       -> ("pInstance" ::: Ptr (Ptr Instance_T))
       -> IO Result))
 -> ContT
      Instance
      IO
      (FunPtr
         (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
          -> ("pAllocator" ::: Ptr AllocationCallbacks)
          -> ("pInstance" ::: Ptr (Ptr Instance_T))
          -> IO Result)))
-> IO
     (FunPtr
        (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
         -> ("pAllocator" ::: Ptr AllocationCallbacks)
         -> ("pInstance" ::: Ptr (Ptr Instance_T))
         -> IO Result))
-> ContT
     Instance
     IO
     (FunPtr
        (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
         -> ("pAllocator" ::: Ptr AllocationCallbacks)
         -> ("pInstance" ::: Ptr (Ptr Instance_T))
         -> IO Result))
forall a b. (a -> b) -> a -> b
$ FunPtr FN_vkVoidFunction
-> FunPtr
     (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pInstance" ::: Ptr (Ptr Instance_T))
      -> IO Result)
forall a b. FunPtr a -> FunPtr b
castFunPtr @_ @(("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pInstance" ::: Ptr (Ptr Instance_T)) -> IO Result) (FunPtr FN_vkVoidFunction
 -> FunPtr
      (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
       -> ("pAllocator" ::: Ptr AllocationCallbacks)
       -> ("pInstance" ::: Ptr (Ptr Instance_T))
       -> IO Result))
-> IO (FunPtr FN_vkVoidFunction)
-> IO
     (FunPtr
        (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
         -> ("pAllocator" ::: Ptr AllocationCallbacks)
         -> ("pInstance" ::: Ptr (Ptr Instance_T))
         -> IO Result))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Instance_T
-> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction)
getInstanceProcAddr' Ptr Instance_T
forall a. Ptr a
nullPtr (Addr# -> "pName" ::: Ptr CChar
forall a. Addr# -> Ptr a
Ptr "vkCreateInstance"#)
  IO () -> ContT Instance IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Instance IO ()) -> IO () -> ContT Instance IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> IO Result)
vkCreateInstancePtr FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> IO Result)
-> FunPtr
     (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pInstance" ::: Ptr (Ptr Instance_T))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> 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 vkCreateInstance is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateInstance' :: ("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pInstance" ::: Ptr (Ptr Instance_T))
-> IO Result
vkCreateInstance' = FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> IO Result)
-> ("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pInstance" ::: Ptr (Ptr Instance_T))
-> IO Result
mkVkCreateInstance FunPtr
  (("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pInstance" ::: Ptr (Ptr Instance_T))
   -> IO Result)
vkCreateInstancePtr
  Ptr (InstanceCreateInfo a)
pCreateInfo <- ((Ptr (InstanceCreateInfo a) -> IO Instance) -> IO Instance)
-> ContT Instance IO (Ptr (InstanceCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (InstanceCreateInfo a) -> IO Instance) -> IO Instance)
 -> ContT Instance IO (Ptr (InstanceCreateInfo a)))
-> ((Ptr (InstanceCreateInfo a) -> IO Instance) -> IO Instance)
-> ContT Instance IO (Ptr (InstanceCreateInfo a))
forall a b. (a -> b) -> a -> b
$ InstanceCreateInfo a
-> (Ptr (InstanceCreateInfo a) -> IO Instance) -> IO Instance
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (InstanceCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Instance IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Instance)
 -> IO Instance)
-> ContT Instance IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Instance)
  -> IO Instance)
 -> ContT Instance IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Instance)
    -> IO Instance)
-> ContT Instance IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Instance)
-> IO Instance
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pInstance" ::: Ptr (Ptr Instance_T)
pPInstance <- ((("pInstance" ::: Ptr (Ptr Instance_T)) -> IO Instance)
 -> IO Instance)
-> ContT Instance IO ("pInstance" ::: Ptr (Ptr Instance_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInstance" ::: Ptr (Ptr Instance_T)) -> IO Instance)
  -> IO Instance)
 -> ContT Instance IO ("pInstance" ::: Ptr (Ptr Instance_T)))
-> ((("pInstance" ::: Ptr (Ptr Instance_T)) -> IO Instance)
    -> IO Instance)
-> ContT Instance IO ("pInstance" ::: Ptr (Ptr Instance_T))
forall a b. (a -> b) -> a -> b
$ IO ("pInstance" ::: Ptr (Ptr Instance_T))
-> (("pInstance" ::: Ptr (Ptr Instance_T)) -> IO ())
-> (("pInstance" ::: Ptr (Ptr Instance_T)) -> IO Instance)
-> IO Instance
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pInstance" ::: Ptr (Ptr Instance_T))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr Instance_T) 8) ("pInstance" ::: Ptr (Ptr Instance_T)) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Instance IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Instance IO Result)
-> IO Result -> ContT Instance IO Result
forall a b. (a -> b) -> a -> b
$ ("pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pInstance" ::: Ptr (Ptr Instance_T))
-> IO Result
vkCreateInstance' (Ptr (InstanceCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct InstanceCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (InstanceCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pInstance" ::: Ptr (Ptr Instance_T)
pPInstance)
  IO () -> ContT Instance IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Instance IO ()) -> IO () -> ContT Instance 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))
  Ptr Instance_T
pInstance <- IO (Ptr Instance_T) -> ContT Instance IO (Ptr Instance_T)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr Instance_T) -> ContT Instance IO (Ptr Instance_T))
-> IO (Ptr Instance_T) -> ContT Instance IO (Ptr Instance_T)
forall a b. (a -> b) -> a -> b
$ ("pInstance" ::: Ptr (Ptr Instance_T)) -> IO (Ptr Instance_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Instance_T) "pInstance" ::: Ptr (Ptr Instance_T)
pPInstance
  Instance
pInstance' <- IO Instance -> ContT Instance IO Instance
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Instance -> ContT Instance IO Instance)
-> IO Instance -> ContT Instance IO Instance
forall a b. (a -> b) -> a -> b
$ (\h :: Ptr Instance_T
h -> Ptr Instance_T -> InstanceCmds -> Instance
Instance Ptr Instance_T
h (InstanceCmds -> Instance) -> IO InstanceCmds -> IO Instance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Instance_T -> IO InstanceCmds
initInstanceCmds Ptr Instance_T
h) Ptr Instance_T
pInstance
  Instance -> ContT Instance IO Instance
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Instance -> ContT Instance IO Instance)
-> Instance -> ContT Instance IO Instance
forall a b. (a -> b) -> a -> b
$ (Instance
pInstance')

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createInstance' and 'destroyInstance'
--
-- To ensure that 'destroyInstance' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withInstance :: forall a io r . (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) => InstanceCreateInfo a -> Maybe AllocationCallbacks -> (io (Instance) -> ((Instance) -> io ()) -> r) -> r
withInstance :: InstanceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Instance -> (Instance -> io ()) -> r)
-> r
withInstance pCreateInfo :: InstanceCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io Instance -> (Instance -> io ()) -> r
b =
  io Instance -> (Instance -> io ()) -> r
b (InstanceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance
forall (a :: [*]) (io :: * -> *).
(Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) =>
InstanceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance
createInstance InstanceCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(Instance
o0) -> Instance -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Instance -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyInstance Instance
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyInstance
  :: FunPtr (Ptr Instance_T -> Ptr AllocationCallbacks -> IO ()) -> Ptr Instance_T -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyInstance - Destroy an instance of Vulkan
--
-- == Valid Usage
--
-- -   All child objects created using @instance@ /must/ have been
--     destroyed prior to destroying @instance@
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @instance@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @instance@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   If @instance@ is not @NULL@, @instance@ /must/ be a valid
--     'Vulkan.Core10.Handles.Instance' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- == Host Synchronization
--
-- -   Host access to @instance@ /must/ be externally synchronized
--
-- -   Host access to all 'Vulkan.Core10.Handles.PhysicalDevice' objects
--     enumerated from @instance@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Instance'
destroyInstance :: forall io
                 . (MonadIO io)
                => -- | @instance@ is the handle of the instance to destroy.
                   Instance
                -> -- | @pAllocator@ controls host memory allocation as described in the
                   -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                   -- chapter.
                   ("allocator" ::: Maybe AllocationCallbacks)
                -> io ()
destroyInstance :: Instance -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyInstance instance' :: Instance
instance' allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyInstancePtr :: FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyInstancePtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyInstance (Instance -> InstanceCmds
instanceCmds (Instance
instance' :: Instance))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyInstancePtr FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
     (Ptr Instance_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
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 vkDestroyInstance is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyInstance' :: Ptr Instance_T
-> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyInstance' = FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Instance_T
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyInstance FunPtr
  (Ptr Instance_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyInstancePtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyInstance' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkEnumeratePhysicalDevices
  :: FunPtr (Ptr Instance_T -> Ptr Word32 -> Ptr (Ptr PhysicalDevice_T) -> IO Result) -> Ptr Instance_T -> Ptr Word32 -> Ptr (Ptr PhysicalDevice_T) -> IO Result

-- | vkEnumeratePhysicalDevices - Enumerates the physical devices accessible
-- to a Vulkan instance
--
-- = Description
--
-- If @pPhysicalDevices@ is @NULL@, then the number of physical devices
-- available is returned in @pPhysicalDeviceCount@. Otherwise,
-- @pPhysicalDeviceCount@ /must/ point to a variable set by the user to the
-- number of elements in the @pPhysicalDevices@ array, and on return the
-- variable is overwritten with the number of handles actually written to
-- @pPhysicalDevices@. If @pPhysicalDeviceCount@ is less than the number of
-- physical devices available, at most @pPhysicalDeviceCount@ structures
-- will be written. If @pPhysicalDeviceCount@ is smaller than the number of
-- physical devices available, 'Vulkan.Core10.Enums.Result.INCOMPLETE' will
-- be returned instead of 'Vulkan.Core10.Enums.Result.SUCCESS', to indicate
-- that not all the available physical devices were returned.
--
-- == Valid Usage (Implicit)
--
-- -   @instance@ /must/ be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   @pPhysicalDeviceCount@ /must/ be a valid pointer to a @uint32_t@
--     value
--
-- -   If the value referenced by @pPhysicalDeviceCount@ is not @0@, and
--     @pPhysicalDevices@ is not @NULL@, @pPhysicalDevices@ /must/ be a
--     valid pointer to an array of @pPhysicalDeviceCount@
--     'Vulkan.Core10.Handles.PhysicalDevice' handles
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INITIALIZATION_FAILED'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Instance', 'Vulkan.Core10.Handles.PhysicalDevice'
enumeratePhysicalDevices :: forall io
                          . (MonadIO io)
                         => -- | @instance@ is a handle to a Vulkan instance previously created with
                            -- 'createInstance'.
                            Instance
                         -> io (Result, ("physicalDevices" ::: Vector PhysicalDevice))
enumeratePhysicalDevices :: Instance
-> io (Result, "physicalDevices" ::: Vector PhysicalDevice)
enumeratePhysicalDevices instance' :: Instance
instance' = IO (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> io (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "physicalDevices" ::: Vector PhysicalDevice)
 -> io (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> (ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
      IO
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
    -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> io (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "physicalDevices" ::: Vector PhysicalDevice)
  IO
  (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> IO (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "physicalDevices" ::: Vector PhysicalDevice)
   IO
   (Result, "physicalDevices" ::: Vector PhysicalDevice)
 -> io (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> io (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall a b. (a -> b) -> a -> b
$ do
  let cmds :: InstanceCmds
cmds = Instance -> InstanceCmds
instanceCmds (Instance
instance' :: Instance)
  let vkEnumeratePhysicalDevicesPtr :: FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO Result)
vkEnumeratePhysicalDevicesPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pPhysicalDeviceCount" ::: Ptr Word32)
      -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
      -> IO Result)
pVkEnumeratePhysicalDevices InstanceCmds
cmds
  IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ())
-> IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO Result)
vkEnumeratePhysicalDevicesPtr FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO Result)
-> FunPtr
     (Ptr Instance_T
      -> ("pPhysicalDeviceCount" ::: Ptr Word32)
      -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> 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 vkEnumeratePhysicalDevices is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkEnumeratePhysicalDevices' :: Ptr Instance_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> IO Result
vkEnumeratePhysicalDevices' = FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO Result)
-> Ptr Instance_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> IO Result
mkVkEnumeratePhysicalDevices FunPtr
  (Ptr Instance_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO Result)
vkEnumeratePhysicalDevicesPtr
  let instance'' :: Ptr Instance_T
instance'' = Instance -> Ptr Instance_T
instanceHandle (Instance
instance')
  "pPhysicalDeviceCount" ::: Ptr Word32
pPPhysicalDeviceCount <- ((("pPhysicalDeviceCount" ::: Ptr Word32)
  -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
 -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("pPhysicalDeviceCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPhysicalDeviceCount" ::: Ptr Word32)
   -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
  -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
      IO
      ("pPhysicalDeviceCount" ::: Ptr Word32))
-> ((("pPhysicalDeviceCount" ::: Ptr Word32)
     -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
    -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("pPhysicalDeviceCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pPhysicalDeviceCount" ::: Ptr Word32)
-> (("pPhysicalDeviceCount" ::: Ptr Word32) -> IO ())
-> (("pPhysicalDeviceCount" ::: Ptr Word32)
    -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> IO (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPhysicalDeviceCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result)
-> IO Result
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> IO Result
vkEnumeratePhysicalDevices' Ptr Instance_T
instance'' ("pPhysicalDeviceCount" ::: Ptr Word32
pPPhysicalDeviceCount) ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)
forall a. Ptr a
nullPtr)
  IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ())
-> IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) 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
pPhysicalDeviceCount <- IO Word32
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32)
-> IO Word32
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPhysicalDeviceCount" ::: Ptr Word32
pPPhysicalDeviceCount
  "pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)
pPPhysicalDevices <- ((("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
  -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
 -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
   -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
  -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
      IO
      ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)))
-> ((("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
     -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
    -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
forall a b. (a -> b) -> a -> b
$ IO ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> (("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)) -> IO ())
-> (("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
    -> IO (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> IO (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr PhysicalDevice_T) ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPhysicalDeviceCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r' <- IO Result
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result)
-> IO Result
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> IO Result
vkEnumeratePhysicalDevices' Ptr Instance_T
instance'' ("pPhysicalDeviceCount" ::: Ptr Word32
pPPhysicalDeviceCount) ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)
pPPhysicalDevices)
  IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO ())
-> IO ()
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) 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
pPhysicalDeviceCount' <- IO Word32
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32)
-> IO Word32
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPhysicalDeviceCount" ::: Ptr Word32
pPPhysicalDeviceCount
  "physicalDevices" ::: Vector PhysicalDevice
pPhysicalDevices' <- IO ("physicalDevices" ::: Vector PhysicalDevice)
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("physicalDevices" ::: Vector PhysicalDevice)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("physicalDevices" ::: Vector PhysicalDevice)
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
      IO
      ("physicalDevices" ::: Vector PhysicalDevice))
-> IO ("physicalDevices" ::: Vector PhysicalDevice)
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     ("physicalDevices" ::: Vector PhysicalDevice)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO PhysicalDevice)
-> IO ("physicalDevices" ::: Vector PhysicalDevice)
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
pPhysicalDeviceCount')) (\i :: Int
i -> do
    Ptr PhysicalDevice_T
pPhysicalDevicesElem <- ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> IO (Ptr PhysicalDevice_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDevice_T) (("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)
pPPhysicalDevices ("pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T))
-> Int -> "pPhysicalDevices" ::: Ptr (Ptr PhysicalDevice_T)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr PhysicalDevice_T)))
    PhysicalDevice -> IO PhysicalDevice
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevice -> IO PhysicalDevice)
-> PhysicalDevice -> IO PhysicalDevice
forall a b. (a -> b) -> a -> b
$ (\h :: Ptr PhysicalDevice_T
h -> Ptr PhysicalDevice_T -> InstanceCmds -> PhysicalDevice
PhysicalDevice Ptr PhysicalDevice_T
h InstanceCmds
cmds ) Ptr PhysicalDevice_T
pPhysicalDevicesElem)
  (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "physicalDevices" ::: Vector PhysicalDevice)
 -> ContT
      (Result, "physicalDevices" ::: Vector PhysicalDevice)
      IO
      (Result, "physicalDevices" ::: Vector PhysicalDevice))
-> (Result, "physicalDevices" ::: Vector PhysicalDevice)
-> ContT
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
     IO
     (Result, "physicalDevices" ::: Vector PhysicalDevice)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "physicalDevices" ::: Vector PhysicalDevice
pPhysicalDevices')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceProcAddr
  :: FunPtr (Ptr Device_T -> Ptr CChar -> IO PFN_vkVoidFunction) -> Ptr Device_T -> Ptr CChar -> IO PFN_vkVoidFunction

-- | vkGetDeviceProcAddr - Return a function pointer for a command
--
-- = Parameters
--
-- The table below defines the various use cases for 'getDeviceProcAddr'
-- and expected return value for each case.
--
-- = Description
--
-- The returned function pointer is of type
-- 'Vulkan.Core10.FuncPointers.PFN_vkVoidFunction', and /must/ be cast to
-- the type of the command being queried before use. The function pointer
-- /must/ only be called with a dispatchable object (the first parameter)
-- that is @device@ or a child of @device@.
--
-- +----------------------+----------------------+-----------------------+
-- | @device@             | @pName@              | return value          |
-- +======================+======================+=======================+
-- | @NULL@               | *1                   | undefined             |
-- +----------------------+----------------------+-----------------------+
-- | invalid device       | *1                   | undefined             |
-- +----------------------+----------------------+-----------------------+
-- | device               | @NULL@               | undefined             |
-- +----------------------+----------------------+-----------------------+
-- | device               | core device-level    | fp2                   |
-- |                      | Vulkan command       |                       |
-- +----------------------+----------------------+-----------------------+
-- | device               | enabled extension    | fp2                   |
-- |                      | device-level         |                       |
-- |                      | commands             |                       |
-- +----------------------+----------------------+-----------------------+
-- | any other case, not  | @NULL@               |                       |
-- | covered above        |                      |                       |
-- +----------------------+----------------------+-----------------------+
--
-- 'getDeviceProcAddr' behavior
--
-- [1]
--     \"*\" means any representable value for the parameter (including
--     valid values, invalid values, and @NULL@).
--
-- [2]
--     The returned function pointer /must/ only be called with a
--     dispatchable object (the first parameter) that is @device@ or a
--     child of @device@ e.g. 'Vulkan.Core10.Handles.Device',
--     'Vulkan.Core10.Handles.Queue', or
--     'Vulkan.Core10.Handles.CommandBuffer'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FuncPointers.PFN_vkVoidFunction',
-- 'Vulkan.Core10.Handles.Device'
getDeviceProcAddr :: forall io
                   . (MonadIO io)
                  => -- | @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                     Device
                  -> -- | @pName@ /must/ be a null-terminated UTF-8 string
                     ("name" ::: ByteString)
                  -> io (PFN_vkVoidFunction)
getDeviceProcAddr :: Device -> ("name" ::: ByteString) -> io (FunPtr FN_vkVoidFunction)
getDeviceProcAddr device :: Device
device name :: "name" ::: ByteString
name = IO (FunPtr FN_vkVoidFunction) -> io (FunPtr FN_vkVoidFunction)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FunPtr FN_vkVoidFunction) -> io (FunPtr FN_vkVoidFunction))
-> (ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
    -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> io (FunPtr FN_vkVoidFunction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> IO (FunPtr FN_vkVoidFunction)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
 -> io (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> io (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceProcAddrPtr :: FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetDeviceProcAddrPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
pVkGetDeviceProcAddr (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (FunPtr FN_vkVoidFunction) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (FunPtr FN_vkVoidFunction) IO ())
-> IO () -> ContT (FunPtr FN_vkVoidFunction) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetDeviceProcAddrPtr FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> FunPtr
     (Ptr Device_T
      -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
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 vkGetDeviceProcAddr is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceProcAddr' :: Ptr Device_T
-> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction)
vkGetDeviceProcAddr' = FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> Ptr Device_T
-> ("pName" ::: Ptr CChar)
-> IO (FunPtr FN_vkVoidFunction)
mkVkGetDeviceProcAddr FunPtr
  (Ptr Device_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetDeviceProcAddrPtr
  "pName" ::: Ptr CChar
pName <- ((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
 -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
  -> IO (FunPtr FN_vkVoidFunction))
 -> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
    -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> IO (FunPtr FN_vkVoidFunction)
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
name)
  FunPtr FN_vkVoidFunction
r <- IO (FunPtr FN_vkVoidFunction)
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (FunPtr FN_vkVoidFunction)
 -> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction))
-> IO (FunPtr FN_vkVoidFunction)
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction)
vkGetDeviceProcAddr' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pName" ::: Ptr CChar
pName
  FunPtr FN_vkVoidFunction
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FunPtr FN_vkVoidFunction
 -> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction))
-> FunPtr FN_vkVoidFunction
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ (FunPtr FN_vkVoidFunction
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetInstanceProcAddr
  :: FunPtr (Ptr Instance_T -> Ptr CChar -> IO PFN_vkVoidFunction) -> Ptr Instance_T -> Ptr CChar -> IO PFN_vkVoidFunction

-- | vkGetInstanceProcAddr - Return a function pointer for a command
--
-- = Description
--
-- 'getInstanceProcAddr' itself is obtained in a platform- and loader-
-- specific manner. Typically, the loader library will export this command
-- as a function symbol, so applications /can/ link against the loader
-- library, or load it dynamically and look up the symbol using
-- platform-specific APIs.
--
-- The table below defines the various use cases for 'getInstanceProcAddr'
-- and expected return value (“fp” is “function pointer”) for each case.
--
-- The returned function pointer is of type
-- 'Vulkan.Core10.FuncPointers.PFN_vkVoidFunction', and /must/ be cast to
-- the type of the command being queried before use.
--
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @instance@           | @pName@                                                                 | return value          |
-- +======================+=========================================================================+=======================+
-- | *1                   | @NULL@                                                                  | undefined             |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | invalid non-@NULL@   | *1                                                                      | undefined             |
-- | instance             |                                                                         |                       |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @NULL@               | 'getInstanceProcAddr'                                                   | fp4                   |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @NULL@               | 'Vulkan.Core11.DeviceInitialization.enumerateInstanceVersion'           | fp                    |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @NULL@               | 'Vulkan.Core10.ExtensionDiscovery.enumerateInstanceExtensionProperties' | fp                    |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @NULL@               | 'Vulkan.Core10.LayerDiscovery.enumerateInstanceLayerProperties'         | fp                    |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | @NULL@               | 'createInstance'                                                        | fp                    |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | instance             | core Vulkan command                                                     | fp2                   |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | instance             | enabled instance extension commands for @instance@                      | fp2                   |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | instance             | available device extension3 commands for @instance@                     | fp2                   |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
-- | any other case, not  | @NULL@                                                                  |                       |
-- | covered above        |                                                                         |                       |
-- +----------------------+-------------------------------------------------------------------------+-----------------------+
--
-- 'getInstanceProcAddr' behavior
--
-- [1]
--     \"*\" means any representable value for the parameter (including
--     valid values, invalid values, and @NULL@).
--
-- [2]
--     The returned function pointer /must/ only be called with a
--     dispatchable object (the first parameter) that is @instance@ or a
--     child of @instance@, e.g. 'Vulkan.Core10.Handles.Instance',
--     'Vulkan.Core10.Handles.PhysicalDevice',
--     'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Queue', or
--     'Vulkan.Core10.Handles.CommandBuffer'.
--
-- [3]
--     An “available device extension” is a device extension supported by
--     any physical device enumerated by @instance@.
--
-- [4]
--     Starting with Vulkan 1.2, 'getInstanceProcAddr' can resolve itself
--     with a @NULL@ instance pointer.
--
-- == Valid Usage (Implicit)
--
-- -   If @instance@ is not @NULL@, @instance@ /must/ be a valid
--     'Vulkan.Core10.Handles.Instance' handle
--
-- -   @pName@ /must/ be a null-terminated UTF-8 string
--
-- = See Also
--
-- 'Vulkan.Core10.FuncPointers.PFN_vkVoidFunction',
-- 'Vulkan.Core10.Handles.Instance'
getInstanceProcAddr :: forall io
                     . (MonadIO io)
                    => -- | @instance@ is the instance that the function pointer will be compatible
                       -- with, or @NULL@ for commands not dependent on any instance.
                       Instance
                    -> -- | @pName@ is the name of the command to obtain.
                       ("name" ::: ByteString)
                    -> io (PFN_vkVoidFunction)
getInstanceProcAddr :: Instance
-> ("name" ::: ByteString) -> io (FunPtr FN_vkVoidFunction)
getInstanceProcAddr instance' :: Instance
instance' name :: "name" ::: ByteString
name = IO (FunPtr FN_vkVoidFunction) -> io (FunPtr FN_vkVoidFunction)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FunPtr FN_vkVoidFunction) -> io (FunPtr FN_vkVoidFunction))
-> (ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
    -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> io (FunPtr FN_vkVoidFunction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> IO (FunPtr FN_vkVoidFunction)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
 -> io (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
-> io (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetInstanceProcAddrPtr :: FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetInstanceProcAddrPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
pVkGetInstanceProcAddr (Instance -> InstanceCmds
instanceCmds (Instance
instance' :: Instance))
  IO () -> ContT (FunPtr FN_vkVoidFunction) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (FunPtr FN_vkVoidFunction) IO ())
-> IO () -> ContT (FunPtr FN_vkVoidFunction) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetInstanceProcAddrPtr FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> FunPtr
     (Ptr Instance_T
      -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
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 vkGetInstanceProcAddr is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetInstanceProcAddr' :: Ptr Instance_T
-> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction)
vkGetInstanceProcAddr' = FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> Ptr Instance_T
-> ("pName" ::: Ptr CChar)
-> IO (FunPtr FN_vkVoidFunction)
mkVkGetInstanceProcAddr FunPtr
  (Ptr Instance_T
   -> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
vkGetInstanceProcAddrPtr
  "pName" ::: Ptr CChar
pName <- ((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
 -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
  -> IO (FunPtr FN_vkVoidFunction))
 -> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
    -> IO (FunPtr FN_vkVoidFunction))
-> ContT (FunPtr FN_vkVoidFunction) IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction))
-> IO (FunPtr FN_vkVoidFunction)
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
name)
  FunPtr FN_vkVoidFunction
r <- IO (FunPtr FN_vkVoidFunction)
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (FunPtr FN_vkVoidFunction)
 -> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction))
-> IO (FunPtr FN_vkVoidFunction)
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> ("pName" ::: Ptr CChar) -> IO (FunPtr FN_vkVoidFunction)
vkGetInstanceProcAddr' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pName" ::: Ptr CChar
pName
  FunPtr FN_vkVoidFunction
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FunPtr FN_vkVoidFunction
 -> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction))
-> FunPtr FN_vkVoidFunction
-> ContT (FunPtr FN_vkVoidFunction) IO (FunPtr FN_vkVoidFunction)
forall a b. (a -> b) -> a -> b
$ (FunPtr FN_vkVoidFunction
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceProperties
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr PhysicalDeviceProperties -> IO ()) -> Ptr PhysicalDevice_T -> Ptr PhysicalDeviceProperties -> IO ()

-- | vkGetPhysicalDeviceProperties - Returns properties of a physical device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceProperties'
getPhysicalDeviceProperties :: forall io
                             . (MonadIO io)
                            => -- | @physicalDevice@ is the handle to the physical device whose properties
                               -- will be queried.
                               --
                               -- @physicalDevice@ /must/ be a valid
                               -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                               PhysicalDevice
                            -> io (PhysicalDeviceProperties)
getPhysicalDeviceProperties :: PhysicalDevice -> io PhysicalDeviceProperties
getPhysicalDeviceProperties physicalDevice :: PhysicalDevice
physicalDevice = IO PhysicalDeviceProperties -> io PhysicalDeviceProperties
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PhysicalDeviceProperties -> io PhysicalDeviceProperties)
-> (ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
    -> IO PhysicalDeviceProperties)
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
-> io PhysicalDeviceProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
-> IO PhysicalDeviceProperties
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
 -> io PhysicalDeviceProperties)
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
-> io PhysicalDeviceProperties
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDevicePropertiesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
vkGetPhysicalDevicePropertiesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
pVkGetPhysicalDeviceProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT PhysicalDeviceProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceProperties IO ())
-> IO () -> ContT PhysicalDeviceProperties IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
vkGetPhysicalDevicePropertiesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
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 vkGetPhysicalDeviceProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceProperties' :: Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ()
vkGetPhysicalDeviceProperties' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
-> Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> IO ()
mkVkGetPhysicalDeviceProperties FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ())
vkGetPhysicalDevicePropertiesPtr
  "pProperties" ::: Ptr PhysicalDeviceProperties
pPProperties <- ((("pProperties" ::: Ptr PhysicalDeviceProperties)
  -> IO PhysicalDeviceProperties)
 -> IO PhysicalDeviceProperties)
-> ContT
     PhysicalDeviceProperties
     IO
     ("pProperties" ::: Ptr PhysicalDeviceProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct PhysicalDeviceProperties =>
(("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @PhysicalDeviceProperties)
  IO () -> ContT PhysicalDeviceProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceProperties IO ())
-> IO () -> ContT PhysicalDeviceProperties IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ()
vkGetPhysicalDeviceProperties' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) ("pProperties" ::: Ptr PhysicalDeviceProperties
pPProperties)
  PhysicalDeviceProperties
pProperties <- IO PhysicalDeviceProperties
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PhysicalDeviceProperties
 -> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties)
-> IO PhysicalDeviceProperties
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> IO PhysicalDeviceProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceProperties "pProperties" ::: Ptr PhysicalDeviceProperties
pPProperties
  PhysicalDeviceProperties
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceProperties
 -> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties)
-> PhysicalDeviceProperties
-> ContT PhysicalDeviceProperties IO PhysicalDeviceProperties
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceProperties
pProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceQueueFamilyProperties
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr QueueFamilyProperties -> IO ()) -> Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr QueueFamilyProperties -> IO ()

-- | vkGetPhysicalDeviceQueueFamilyProperties - Reports properties of the
-- queues of the specified physical device
--
-- = Description
--
-- If @pQueueFamilyProperties@ is @NULL@, then the number of queue families
-- available is returned in @pQueueFamilyPropertyCount@. Implementations
-- /must/ support at least one queue family. Otherwise,
-- @pQueueFamilyPropertyCount@ /must/ point to a variable set by the user
-- to the number of elements in the @pQueueFamilyProperties@ array, and on
-- return the variable is overwritten with the number of structures
-- actually written to @pQueueFamilyProperties@. If
-- @pQueueFamilyPropertyCount@ is less than the number of queue families
-- available, at most @pQueueFamilyPropertyCount@ structures will be
-- written.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pQueueFamilyPropertyCount@ /must/ be a valid pointer to a
--     @uint32_t@ value
--
-- -   If the value referenced by @pQueueFamilyPropertyCount@ is not @0@,
--     and @pQueueFamilyProperties@ is not @NULL@, @pQueueFamilyProperties@
--     /must/ be a valid pointer to an array of @pQueueFamilyPropertyCount@
--     'QueueFamilyProperties' structures
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'QueueFamilyProperties'
getPhysicalDeviceQueueFamilyProperties :: forall io
                                        . (MonadIO io)
                                       => -- | @physicalDevice@ is the handle to the physical device whose properties
                                          -- will be queried.
                                          PhysicalDevice
                                       -> io (("queueFamilyProperties" ::: Vector QueueFamilyProperties))
getPhysicalDeviceQueueFamilyProperties :: PhysicalDevice
-> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
getPhysicalDeviceQueueFamilyProperties physicalDevice :: PhysicalDevice
physicalDevice = IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
 -> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> (ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
  IO
  ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
   IO
   ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
 -> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceQueueFamilyPropertiesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
vkGetPhysicalDeviceQueueFamilyPropertiesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pPhysicalDeviceCount" ::: Ptr Word32)
      -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
      -> IO ())
pVkGetPhysicalDeviceQueueFamilyProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
vkGetPhysicalDeviceQueueFamilyPropertiesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pPhysicalDeviceCount" ::: Ptr Word32)
      -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
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 vkGetPhysicalDeviceQueueFamilyProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceQueueFamilyProperties' :: Ptr PhysicalDevice_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO ()
mkVkGetPhysicalDeviceQueueFamilyProperties FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPhysicalDeviceCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ())
vkGetPhysicalDeviceQueueFamilyPropertiesPtr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  "pPhysicalDeviceCount" ::: Ptr Word32
pPQueueFamilyPropertyCount <- ((("pPhysicalDeviceCount" ::: Ptr Word32)
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("pPhysicalDeviceCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPhysicalDeviceCount" ::: Ptr Word32)
   -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      ("pPhysicalDeviceCount" ::: Ptr Word32))
-> ((("pPhysicalDeviceCount" ::: Ptr Word32)
     -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("pPhysicalDeviceCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pPhysicalDeviceCount" ::: Ptr Word32)
-> (("pPhysicalDeviceCount" ::: Ptr Word32) -> IO ())
-> (("pPhysicalDeviceCount" ::: Ptr Word32)
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPhysicalDeviceCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties' Ptr PhysicalDevice_T
physicalDevice' ("pPhysicalDeviceCount" ::: Ptr Word32
pPQueueFamilyPropertyCount) ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
forall a. Ptr a
nullPtr)
  Word32
pQueueFamilyPropertyCount <- IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      Word32)
-> IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPhysicalDeviceCount" ::: Ptr Word32
pPQueueFamilyPropertyCount
  "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
pPQueueFamilyProperties <- ((("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
   -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties))
-> ((("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
     -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
forall a b. (a -> b) -> a -> b
$ IO ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
    -> IO ())
-> (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
forall a. Int -> IO (Ptr a)
callocBytes @QueueFamilyProperties ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pQueueFamilyPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24)) ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties) -> IO ()
forall a. Ptr a -> IO ()
free
  [()]
_ <- (Int
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ())
-> [Int]
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
   -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
  -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ())
-> ((()
     -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall a b. (a -> b) -> a -> b
$ ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
pPQueueFamilyProperties ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) :: Ptr QueueFamilyProperties) (IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
 -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ((()
     -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> (()
    -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
 -> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ()
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pQueueFamilyPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pPhysicalDeviceCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties' Ptr PhysicalDevice_T
physicalDevice' ("pPhysicalDeviceCount" ::: Ptr Word32
pPQueueFamilyPropertyCount) (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
pPQueueFamilyProperties))
  Word32
pQueueFamilyPropertyCount' <- IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      Word32)
-> IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPhysicalDeviceCount" ::: Ptr Word32
pPQueueFamilyPropertyCount
  "queueFamilyProperties" ::: Vector QueueFamilyProperties
pQueueFamilyProperties' <- IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO QueueFamilyProperties)
-> IO ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
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
pQueueFamilyPropertyCount')) (\i :: Int
i -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO QueueFamilyProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @QueueFamilyProperties ((("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
pPQueueFamilyProperties) ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr QueueFamilyProperties)))
  ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("queueFamilyProperties" ::: Vector QueueFamilyProperties)
 -> ContT
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
      IO
      ("queueFamilyProperties" ::: Vector QueueFamilyProperties))
-> ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
-> ContT
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
     IO
     ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
forall a b. (a -> b) -> a -> b
$ ("queueFamilyProperties" ::: Vector QueueFamilyProperties
pQueueFamilyProperties')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceMemoryProperties
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr PhysicalDeviceMemoryProperties -> IO ()) -> Ptr PhysicalDevice_T -> Ptr PhysicalDeviceMemoryProperties -> IO ()

-- | vkGetPhysicalDeviceMemoryProperties - Reports memory information for the
-- specified physical device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceMemoryProperties'
getPhysicalDeviceMemoryProperties :: forall io
                                   . (MonadIO io)
                                  => -- | @physicalDevice@ is the handle to the device to query.
                                     --
                                     -- @physicalDevice@ /must/ be a valid
                                     -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                     PhysicalDevice
                                  -> io (PhysicalDeviceMemoryProperties)
getPhysicalDeviceMemoryProperties :: PhysicalDevice -> io PhysicalDeviceMemoryProperties
getPhysicalDeviceMemoryProperties physicalDevice :: PhysicalDevice
physicalDevice = IO PhysicalDeviceMemoryProperties
-> io PhysicalDeviceMemoryProperties
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PhysicalDeviceMemoryProperties
 -> io PhysicalDeviceMemoryProperties)
-> (ContT
      PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
    -> IO PhysicalDeviceMemoryProperties)
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
-> io PhysicalDeviceMemoryProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
-> IO PhysicalDeviceMemoryProperties
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
 -> io PhysicalDeviceMemoryProperties)
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
-> io PhysicalDeviceMemoryProperties
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceMemoryPropertiesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
vkGetPhysicalDeviceMemoryPropertiesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
      -> IO ())
pVkGetPhysicalDeviceMemoryProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT PhysicalDeviceMemoryProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceMemoryProperties IO ())
-> IO () -> ContT PhysicalDeviceMemoryProperties IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
vkGetPhysicalDeviceMemoryPropertiesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
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 vkGetPhysicalDeviceMemoryProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceMemoryProperties' :: Ptr PhysicalDevice_T
-> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO ()
vkGetPhysicalDeviceMemoryProperties' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO ()
mkVkGetPhysicalDeviceMemoryProperties FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
   -> IO ())
vkGetPhysicalDeviceMemoryPropertiesPtr
  "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
pPMemoryProperties <- ((("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
  -> IO PhysicalDeviceMemoryProperties)
 -> IO PhysicalDeviceMemoryProperties)
-> ContT
     PhysicalDeviceMemoryProperties
     IO
     ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct PhysicalDeviceMemoryProperties =>
(("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
 -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @PhysicalDeviceMemoryProperties)
  IO () -> ContT PhysicalDeviceMemoryProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceMemoryProperties IO ())
-> IO () -> ContT PhysicalDeviceMemoryProperties IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO ()
vkGetPhysicalDeviceMemoryProperties' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
pPMemoryProperties)
  PhysicalDeviceMemoryProperties
pMemoryProperties <- IO PhysicalDeviceMemoryProperties
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PhysicalDeviceMemoryProperties
 -> ContT
      PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties)
-> IO PhysicalDeviceMemoryProperties
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
forall a b. (a -> b) -> a -> b
$ ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO PhysicalDeviceMemoryProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceMemoryProperties "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
pPMemoryProperties
  PhysicalDeviceMemoryProperties
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryProperties
 -> ContT
      PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties)
-> PhysicalDeviceMemoryProperties
-> ContT
     PhysicalDeviceMemoryProperties IO PhysicalDeviceMemoryProperties
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceMemoryProperties
pMemoryProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceFeatures
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr PhysicalDeviceFeatures -> IO ()) -> Ptr PhysicalDevice_T -> Ptr PhysicalDeviceFeatures -> IO ()

-- | vkGetPhysicalDeviceFeatures - Reports capabilities of a physical device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceFeatures'
getPhysicalDeviceFeatures :: forall io
                           . (MonadIO io)
                          => -- | @physicalDevice@ is the physical device from which to query the
                             -- supported features.
                             --
                             -- @physicalDevice@ /must/ be a valid
                             -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                             PhysicalDevice
                          -> io (PhysicalDeviceFeatures)
getPhysicalDeviceFeatures :: PhysicalDevice -> io PhysicalDeviceFeatures
getPhysicalDeviceFeatures physicalDevice :: PhysicalDevice
physicalDevice = IO PhysicalDeviceFeatures -> io PhysicalDeviceFeatures
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PhysicalDeviceFeatures -> io PhysicalDeviceFeatures)
-> (ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
    -> IO PhysicalDeviceFeatures)
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
-> io PhysicalDeviceFeatures
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
-> IO PhysicalDeviceFeatures
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
 -> io PhysicalDeviceFeatures)
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
-> io PhysicalDeviceFeatures
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceFeaturesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
vkGetPhysicalDeviceFeaturesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
pVkGetPhysicalDeviceFeatures (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT PhysicalDeviceFeatures IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceFeatures IO ())
-> IO () -> ContT PhysicalDeviceFeatures IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
vkGetPhysicalDeviceFeaturesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
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 vkGetPhysicalDeviceFeatures is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceFeatures' :: Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ()
vkGetPhysicalDeviceFeatures' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
-> Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> IO ()
mkVkGetPhysicalDeviceFeatures FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ())
vkGetPhysicalDeviceFeaturesPtr
  "pFeatures" ::: Ptr PhysicalDeviceFeatures
pPFeatures <- ((("pFeatures" ::: Ptr PhysicalDeviceFeatures)
  -> IO PhysicalDeviceFeatures)
 -> IO PhysicalDeviceFeatures)
-> ContT
     PhysicalDeviceFeatures
     IO
     ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct PhysicalDeviceFeatures =>
(("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @PhysicalDeviceFeatures)
  IO () -> ContT PhysicalDeviceFeatures IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PhysicalDeviceFeatures IO ())
-> IO () -> ContT PhysicalDeviceFeatures IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO ()
vkGetPhysicalDeviceFeatures' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) ("pFeatures" ::: Ptr PhysicalDeviceFeatures
pPFeatures)
  PhysicalDeviceFeatures
pFeatures <- IO PhysicalDeviceFeatures
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PhysicalDeviceFeatures
 -> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures)
-> IO PhysicalDeviceFeatures
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
forall a b. (a -> b) -> a -> b
$ ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> IO PhysicalDeviceFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceFeatures "pFeatures" ::: Ptr PhysicalDeviceFeatures
pPFeatures
  PhysicalDeviceFeatures
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceFeatures
 -> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures
-> ContT PhysicalDeviceFeatures IO PhysicalDeviceFeatures
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceFeatures
pFeatures)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceFormatProperties
  :: FunPtr (Ptr PhysicalDevice_T -> Format -> Ptr FormatProperties -> IO ()) -> Ptr PhysicalDevice_T -> Format -> Ptr FormatProperties -> IO ()

-- | vkGetPhysicalDeviceFormatProperties - Lists physical device’s format
-- capabilities
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format', 'FormatProperties',
-- 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceFormatProperties :: forall io
                                   . (MonadIO io)
                                  => -- | @physicalDevice@ is the physical device from which to query the format
                                     -- properties.
                                     --
                                     -- @physicalDevice@ /must/ be a valid
                                     -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                     PhysicalDevice
                                  -> -- | @format@ is the format whose properties are queried.
                                     --
                                     -- @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
                                     Format
                                  -> io (FormatProperties)
getPhysicalDeviceFormatProperties :: PhysicalDevice -> Format -> io FormatProperties
getPhysicalDeviceFormatProperties physicalDevice :: PhysicalDevice
physicalDevice format :: Format
format = IO FormatProperties -> io FormatProperties
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FormatProperties -> io FormatProperties)
-> (ContT FormatProperties IO FormatProperties
    -> IO FormatProperties)
-> ContT FormatProperties IO FormatProperties
-> io FormatProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT FormatProperties IO FormatProperties -> IO FormatProperties
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT FormatProperties IO FormatProperties -> io FormatProperties)
-> ContT FormatProperties IO FormatProperties
-> io FormatProperties
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceFormatPropertiesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
vkGetPhysicalDeviceFormatPropertiesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ("pFormatProperties" ::: Ptr FormatProperties)
      -> IO ())
pVkGetPhysicalDeviceFormatProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT FormatProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT FormatProperties IO ())
-> IO () -> ContT FormatProperties IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
vkGetPhysicalDeviceFormatPropertiesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ("pFormatProperties" ::: Ptr FormatProperties)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
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 vkGetPhysicalDeviceFormatProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceFormatProperties' :: Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr FormatProperties)
-> IO ()
vkGetPhysicalDeviceFormatProperties' = FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
-> Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr FormatProperties)
-> IO ()
mkVkGetPhysicalDeviceFormatProperties FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr FormatProperties)
   -> IO ())
vkGetPhysicalDeviceFormatPropertiesPtr
  "pFormatProperties" ::: Ptr FormatProperties
pPFormatProperties <- ((("pFormatProperties" ::: Ptr FormatProperties)
  -> IO FormatProperties)
 -> IO FormatProperties)
-> ContT
     FormatProperties IO ("pFormatProperties" ::: Ptr FormatProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct FormatProperties =>
(("pFormatProperties" ::: Ptr FormatProperties) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @FormatProperties)
  IO () -> ContT FormatProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT FormatProperties IO ())
-> IO () -> ContT FormatProperties IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr FormatProperties)
-> IO ()
vkGetPhysicalDeviceFormatProperties' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Format
format) ("pFormatProperties" ::: Ptr FormatProperties
pPFormatProperties)
  FormatProperties
pFormatProperties <- IO FormatProperties -> ContT FormatProperties IO FormatProperties
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO FormatProperties -> ContT FormatProperties IO FormatProperties)
-> IO FormatProperties
-> ContT FormatProperties IO FormatProperties
forall a b. (a -> b) -> a -> b
$ ("pFormatProperties" ::: Ptr FormatProperties)
-> IO FormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @FormatProperties "pFormatProperties" ::: Ptr FormatProperties
pPFormatProperties
  FormatProperties -> ContT FormatProperties IO FormatProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FormatProperties -> ContT FormatProperties IO FormatProperties)
-> FormatProperties -> ContT FormatProperties IO FormatProperties
forall a b. (a -> b) -> a -> b
$ (FormatProperties
pFormatProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceImageFormatProperties
  :: FunPtr (Ptr PhysicalDevice_T -> Format -> ImageType -> ImageTiling -> ImageUsageFlags -> ImageCreateFlags -> Ptr ImageFormatProperties -> IO Result) -> Ptr PhysicalDevice_T -> Format -> ImageType -> ImageTiling -> ImageUsageFlags -> ImageCreateFlags -> Ptr ImageFormatProperties -> IO Result

-- | vkGetPhysicalDeviceImageFormatProperties - Lists physical device’s image
-- format capabilities
--
-- = Description
--
-- The @format@, @type@, @tiling@, @usage@, and @flags@ parameters
-- correspond to parameters that would be consumed by
-- 'Vulkan.Core10.Image.createImage' (as members of
-- 'Vulkan.Core10.Image.ImageCreateInfo').
--
-- If @format@ is not a supported image format, or if the combination of
-- @format@, @type@, @tiling@, @usage@, and @flags@ is not supported for
-- images, then 'getPhysicalDeviceImageFormatProperties' returns
-- 'Vulkan.Core10.Enums.Result.ERROR_FORMAT_NOT_SUPPORTED'.
--
-- The limitations on an image format that are reported by
-- 'getPhysicalDeviceImageFormatProperties' have the following property: if
-- @usage1@ and @usage2@ of type
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags' are such that
-- the bits set in @usage1@ are a subset of the bits set in @usage2@, and
-- @flags1@ and @flags2@ of type
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlags' are such that
-- the bits set in @flags1@ are a subset of the bits set in @flags2@, then
-- the limitations for @usage1@ and @flags1@ /must/ be no more strict than
-- the limitations for @usage2@ and @flags2@, for all values of @format@,
-- @type@, and @tiling@.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FORMAT_NOT_SUPPORTED'
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlags',
-- 'ImageFormatProperties', 'Vulkan.Core10.Enums.ImageTiling.ImageTiling',
-- 'Vulkan.Core10.Enums.ImageType.ImageType',
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags',
-- 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceImageFormatProperties :: forall io
                                        . (MonadIO io)
                                       => -- | @physicalDevice@ is the physical device from which to query the image
                                          -- capabilities.
                                          --
                                          -- @physicalDevice@ /must/ be a valid
                                          -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                          PhysicalDevice
                                       -> -- | @format@ is a 'Vulkan.Core10.Enums.Format.Format' value specifying the
                                          -- image format, corresponding to
                                          -- 'Vulkan.Core10.Image.ImageCreateInfo'::@format@.
                                          --
                                          -- @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
                                          Format
                                       -> -- | @type@ is a 'Vulkan.Core10.Enums.ImageType.ImageType' value specifying
                                          -- the image type, corresponding to
                                          -- 'Vulkan.Core10.Image.ImageCreateInfo'::@imageType@.
                                          --
                                          -- @type@ /must/ be a valid 'Vulkan.Core10.Enums.ImageType.ImageType' value
                                          ImageType
                                       -> -- | @tiling@ is a 'Vulkan.Core10.Enums.ImageTiling.ImageTiling' value
                                          -- specifying the image tiling, corresponding to
                                          -- 'Vulkan.Core10.Image.ImageCreateInfo'::@tiling@.
                                          --
                                          -- @tiling@ /must/ not be
                                          -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT'.
                                          -- (Use
                                          -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
                                          -- instead)
                                          --
                                          -- @tiling@ /must/ be a valid 'Vulkan.Core10.Enums.ImageTiling.ImageTiling'
                                          -- value
                                          ImageTiling
                                       -> -- | @usage@ is a bitmask of
                                          -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' specifying
                                          -- the intended usage of the image, corresponding to
                                          -- 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@.
                                          --
                                          -- @usage@ /must/ be a valid combination of
                                          -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' values
                                          --
                                          -- @usage@ /must/ not be @0@
                                          ImageUsageFlags
                                       -> -- | @flags@ is a bitmask of
                                          -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlagBits' specifying
                                          -- additional parameters of the image, corresponding to
                                          -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@.
                                          --
                                          -- @flags@ /must/ be a valid combination of
                                          -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlagBits' values
                                          ImageCreateFlags
                                       -> io (ImageFormatProperties)
getPhysicalDeviceImageFormatProperties :: PhysicalDevice
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> io ImageFormatProperties
getPhysicalDeviceImageFormatProperties physicalDevice :: PhysicalDevice
physicalDevice format :: Format
format type' :: ImageType
type' tiling :: ImageTiling
tiling usage :: ImageUsageFlags
usage flags :: ImageCreateFlags
flags = IO ImageFormatProperties -> io ImageFormatProperties
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageFormatProperties -> io ImageFormatProperties)
-> (ContT ImageFormatProperties IO ImageFormatProperties
    -> IO ImageFormatProperties)
-> ContT ImageFormatProperties IO ImageFormatProperties
-> io ImageFormatProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ImageFormatProperties IO ImageFormatProperties
-> IO ImageFormatProperties
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ImageFormatProperties IO ImageFormatProperties
 -> io ImageFormatProperties)
-> ContT ImageFormatProperties IO ImageFormatProperties
-> io ImageFormatProperties
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceImageFormatPropertiesPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> IO Result)
vkGetPhysicalDeviceImageFormatPropertiesPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ImageType
      -> ImageTiling
      -> ImageUsageFlags
      -> ImageCreateFlags
      -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
      -> IO Result)
pVkGetPhysicalDeviceImageFormatProperties (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT ImageFormatProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageFormatProperties IO ())
-> IO () -> ContT ImageFormatProperties IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> IO Result)
vkGetPhysicalDeviceImageFormatPropertiesPtr FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ImageType
      -> ImageTiling
      -> ImageUsageFlags
      -> ImageCreateFlags
      -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> 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 vkGetPhysicalDeviceImageFormatProperties is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceImageFormatProperties' :: Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO Result
vkGetPhysicalDeviceImageFormatProperties' = FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> IO Result)
-> Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO Result
mkVkGetPhysicalDeviceImageFormatProperties FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ImageType
   -> ImageTiling
   -> ImageUsageFlags
   -> ImageCreateFlags
   -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
   -> IO Result)
vkGetPhysicalDeviceImageFormatPropertiesPtr
  "pImageFormatProperties" ::: Ptr ImageFormatProperties
pPImageFormatProperties <- ((("pImageFormatProperties" ::: Ptr ImageFormatProperties)
  -> IO ImageFormatProperties)
 -> IO ImageFormatProperties)
-> ContT
     ImageFormatProperties
     IO
     ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct ImageFormatProperties =>
(("pImageFormatProperties" ::: Ptr ImageFormatProperties) -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @ImageFormatProperties)
  Result
r <- IO Result -> ContT ImageFormatProperties IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ImageFormatProperties IO Result)
-> IO Result -> ContT ImageFormatProperties IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO Result
vkGetPhysicalDeviceImageFormatProperties' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Format
format) (ImageType
type') (ImageTiling
tiling) (ImageUsageFlags
usage) (ImageCreateFlags
flags) ("pImageFormatProperties" ::: Ptr ImageFormatProperties
pPImageFormatProperties)
  IO () -> ContT ImageFormatProperties IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageFormatProperties IO ())
-> IO () -> ContT ImageFormatProperties 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))
  ImageFormatProperties
pImageFormatProperties <- IO ImageFormatProperties
-> ContT ImageFormatProperties IO ImageFormatProperties
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ImageFormatProperties
 -> ContT ImageFormatProperties IO ImageFormatProperties)
-> IO ImageFormatProperties
-> ContT ImageFormatProperties IO ImageFormatProperties
forall a b. (a -> b) -> a -> b
$ ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO ImageFormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageFormatProperties "pImageFormatProperties" ::: Ptr ImageFormatProperties
pPImageFormatProperties
  ImageFormatProperties
-> ContT ImageFormatProperties IO ImageFormatProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageFormatProperties
 -> ContT ImageFormatProperties IO ImageFormatProperties)
-> ImageFormatProperties
-> ContT ImageFormatProperties IO ImageFormatProperties
forall a b. (a -> b) -> a -> b
$ (ImageFormatProperties
pImageFormatProperties)


-- | VkPhysicalDeviceProperties - Structure specifying physical device
-- properties
--
-- = Description
--
-- Note
--
-- The value of @apiVersion@ /may/ be different than the version returned
-- by 'Vulkan.Core11.DeviceInitialization.enumerateInstanceVersion'; either
-- higher or lower. In such cases, the application /must/ not use
-- functionality that exceeds the version of Vulkan associated with a given
-- object. The @pApiVersion@ parameter returned by
-- 'Vulkan.Core11.DeviceInitialization.enumerateInstanceVersion' is the
-- version associated with a 'Vulkan.Core10.Handles.Instance' and its
-- children, except for a 'Vulkan.Core10.Handles.PhysicalDevice' and its
-- children. 'PhysicalDeviceProperties'::@apiVersion@ is the version
-- associated with a 'Vulkan.Core10.Handles.PhysicalDevice' and its
-- children.
--
-- The @vendorID@ and @deviceID@ fields are provided to allow applications
-- to adapt to device characteristics that are not adequately exposed by
-- other Vulkan queries.
--
-- Note
--
-- These /may/ include performance profiles, hardware errata, or other
-- characteristics.
--
-- The /vendor/ identified by @vendorID@ is the entity responsible for the
-- most salient characteristics of the underlying implementation of the
-- 'Vulkan.Core10.Handles.PhysicalDevice' being queried.
--
-- Note
--
-- For example, in the case of a discrete GPU implementation, this /should/
-- be the GPU chipset vendor. In the case of a hardware accelerator
-- integrated into a system-on-chip (SoC), this /should/ be the supplier of
-- the silicon IP used to create the accelerator.
--
-- If the vendor has a
-- <https://pcisig.com/membership/member-companies PCI vendor ID>, the low
-- 16 bits of @vendorID@ /must/ contain that PCI vendor ID, and the
-- remaining bits /must/ be set to zero. Otherwise, the value returned
-- /must/ be a valid Khronos vendor ID, obtained as described in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vulkan-styleguide Vulkan Documentation and Extensions: Procedures and Conventions>
-- document in the section “Registering a Vendor ID with Khronos”. Khronos
-- vendor IDs are allocated starting at 0x10000, to distinguish them from
-- the PCI vendor ID namespace. Khronos vendor IDs are symbolically defined
-- in the 'Vulkan.Core10.Enums.VendorId.VendorId' type.
--
-- The vendor is also responsible for the value returned in @deviceID@. If
-- the implementation is driven primarily by a
-- <https://pcisig.com/ PCI device> with a
-- <https://pcisig.com/ PCI device ID>, the low 16 bits of @deviceID@
-- /must/ contain that PCI device ID, and the remaining bits /must/ be set
-- to zero. Otherwise, the choice of what values to return /may/ be
-- dictated by operating system or platform policies - but /should/
-- uniquely identify both the device version and any major configuration
-- options (for example, core count in the case of multicore devices).
--
-- Note
--
-- The same device ID /should/ be used for all physical implementations of
-- that device version and configuration. For example, all uses of a
-- specific silicon IP GPU version and configuration /should/ use the same
-- device ID, even if those uses occur in different SoCs.
--
-- = See Also
--
-- 'PhysicalDeviceLimits',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- 'PhysicalDeviceSparseProperties',
-- 'Vulkan.Core10.Enums.PhysicalDeviceType.PhysicalDeviceType',
-- 'getPhysicalDeviceProperties'
data PhysicalDeviceProperties = PhysicalDeviceProperties
  { -- | @apiVersion@ is the version of Vulkan supported by the device, encoded
    -- as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-coreversions-versionnumbers>.
    PhysicalDeviceProperties -> Word32
apiVersion :: Word32
  , -- | @driverVersion@ is the vendor-specified version of the driver.
    PhysicalDeviceProperties -> Word32
driverVersion :: Word32
  , -- | @vendorID@ is a unique identifier for the /vendor/ (see below) of the
    -- physical device.
    PhysicalDeviceProperties -> Word32
vendorID :: Word32
  , -- | @deviceID@ is a unique identifier for the physical device among devices
    -- available from the vendor.
    PhysicalDeviceProperties -> Word32
deviceID :: Word32
  , -- | @deviceType@ is a
    -- 'Vulkan.Core10.Enums.PhysicalDeviceType.PhysicalDeviceType' specifying
    -- the type of device.
    PhysicalDeviceProperties -> PhysicalDeviceType
deviceType :: PhysicalDeviceType
  , -- | @deviceName@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_PHYSICAL_DEVICE_NAME_SIZE' @char@
    -- containing a null-terminated UTF-8 string which is the name of the
    -- device.
    PhysicalDeviceProperties -> "name" ::: ByteString
deviceName :: ByteString
  , -- | @pipelineCacheUUID@ is an array of
    -- 'Vulkan.Core10.APIConstants.UUID_SIZE' @uint8_t@ values representing a
    -- universally unique identifier for the device.
    PhysicalDeviceProperties -> "name" ::: ByteString
pipelineCacheUUID :: ByteString
  , -- | @limits@ is the 'PhysicalDeviceLimits' structure specifying
    -- device-specific limits of the physical device. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits Limits>
    -- for details.
    PhysicalDeviceProperties -> PhysicalDeviceLimits
limits :: PhysicalDeviceLimits
  , -- | @sparseProperties@ is the 'PhysicalDeviceSparseProperties' structure
    -- specifying various sparse related properties of the physical device. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory-physicalprops Sparse Properties>
    -- for details.
    PhysicalDeviceProperties -> PhysicalDeviceSparseProperties
sparseProperties :: PhysicalDeviceSparseProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceProperties)
#endif
deriving instance Show PhysicalDeviceProperties

instance ToCStruct PhysicalDeviceProperties where
  withCStruct :: PhysicalDeviceProperties
-> (("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceProperties
x f :: ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 824 8 ((("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b)
 -> IO b)
-> (("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr PhysicalDeviceProperties
p -> ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> PhysicalDeviceProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr PhysicalDeviceProperties
p PhysicalDeviceProperties
x (("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b
f "pProperties" ::: Ptr PhysicalDeviceProperties
p)
  pokeCStruct :: ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> PhysicalDeviceProperties -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr PhysicalDeviceProperties
p PhysicalDeviceProperties{..} 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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
apiVersion)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
driverVersion)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
vendorID)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
deviceID)
    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 PhysicalDeviceType -> PhysicalDeviceType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceType)) (PhysicalDeviceType
deviceType)
    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_PHYSICAL_DEVICE_NAME_SIZE CChar)
-> ("name" ::: ByteString) -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ("name" ::: ByteString) -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar))) ("name" ::: ByteString
deviceName)
    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 UUID_SIZE Word8)
-> ("name" ::: ByteString) -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ("name" ::: ByteString) -> IO ()
pokeFixedLengthByteString (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray UUID_SIZE Word8))) ("name" ::: ByteString
pipelineCacheUUID)
    ((() -> 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 PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceLimits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr PhysicalDeviceLimits)) (PhysicalDeviceLimits
limits) (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) -> 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 PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceSparseProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 800 :: Ptr PhysicalDeviceSparseProperties)) (PhysicalDeviceSparseProperties
sparseProperties) (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 = 824
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr PhysicalDeviceProperties
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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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 PhysicalDeviceType -> PhysicalDeviceType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceType)) (PhysicalDeviceType
forall a. Zero a => a
zero)
    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_PHYSICAL_DEVICE_NAME_SIZE CChar)
-> ("name" ::: ByteString) -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ("name" ::: ByteString) -> IO ()
pokeFixedLengthNullTerminatedByteString (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar))) ("name" ::: 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 UUID_SIZE Word8)
-> ("name" ::: ByteString) -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ("name" ::: ByteString) -> IO ()
pokeFixedLengthByteString (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray UUID_SIZE Word8))) ("name" ::: ByteString
forall a. Monoid a => a
mempty)
    ((() -> 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 PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceLimits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr PhysicalDeviceLimits)) (PhysicalDeviceLimits
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) -> 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 PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceSparseProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 800 :: Ptr PhysicalDeviceSparseProperties)) (PhysicalDeviceSparseProperties
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 PhysicalDeviceProperties where
  peekCStruct :: ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> IO PhysicalDeviceProperties
peekCStruct p :: "pProperties" ::: Ptr PhysicalDeviceProperties
p = do
    Word32
apiVersion <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
driverVersion <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
vendorID <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Word32
deviceID <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    PhysicalDeviceType
deviceType <- Ptr PhysicalDeviceType -> IO PhysicalDeviceType
forall a. Storable a => Ptr a -> IO a
peek @PhysicalDeviceType (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceType))
    "name" ::: ByteString
deviceName <- ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
packCString (Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar)
-> "pName" ::: Ptr CChar
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_PHYSICAL_DEVICE_NAME_SIZE CChar))))
    "name" ::: ByteString
pipelineCacheUUID <- Ptr (FixedArray UUID_SIZE Word8) -> IO ("name" ::: ByteString)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ("name" ::: ByteString)
peekByteStringFromSizedVectorPtr (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray UUID_SIZE Word8)))
    PhysicalDeviceLimits
limits <- Ptr PhysicalDeviceLimits -> IO PhysicalDeviceLimits
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceLimits (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceLimits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr PhysicalDeviceLimits))
    PhysicalDeviceSparseProperties
sparseProperties <- Ptr PhysicalDeviceSparseProperties
-> IO PhysicalDeviceSparseProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceSparseProperties (("pProperties" ::: Ptr PhysicalDeviceProperties
p ("pProperties" ::: Ptr PhysicalDeviceProperties)
-> Int -> Ptr PhysicalDeviceSparseProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 800 :: Ptr PhysicalDeviceSparseProperties))
    PhysicalDeviceProperties -> IO PhysicalDeviceProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceProperties -> IO PhysicalDeviceProperties)
-> PhysicalDeviceProperties -> IO PhysicalDeviceProperties
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDeviceType
-> ("name" ::: ByteString)
-> ("name" ::: ByteString)
-> PhysicalDeviceLimits
-> PhysicalDeviceSparseProperties
-> PhysicalDeviceProperties
PhysicalDeviceProperties
             Word32
apiVersion Word32
driverVersion Word32
vendorID Word32
deviceID PhysicalDeviceType
deviceType "name" ::: ByteString
deviceName "name" ::: ByteString
pipelineCacheUUID PhysicalDeviceLimits
limits PhysicalDeviceSparseProperties
sparseProperties

instance Zero PhysicalDeviceProperties where
  zero :: PhysicalDeviceProperties
zero = Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDeviceType
-> ("name" ::: ByteString)
-> ("name" ::: ByteString)
-> PhysicalDeviceLimits
-> PhysicalDeviceSparseProperties
-> PhysicalDeviceProperties
PhysicalDeviceProperties
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           PhysicalDeviceType
forall a. Zero a => a
zero
           "name" ::: ByteString
forall a. Monoid a => a
mempty
           "name" ::: ByteString
forall a. Monoid a => a
mempty
           PhysicalDeviceLimits
forall a. Zero a => a
zero
           PhysicalDeviceSparseProperties
forall a. Zero a => a
zero


-- | VkApplicationInfo - Structure specifying application info
--
-- = Description
--
-- Vulkan 1.0 implementations were required to return
-- 'Vulkan.Core10.Enums.Result.ERROR_INCOMPATIBLE_DRIVER' if @apiVersion@
-- was larger than 1.0. Implementations that support Vulkan 1.1 or later
-- /must/ not return 'Vulkan.Core10.Enums.Result.ERROR_INCOMPATIBLE_DRIVER'
-- for any value of @apiVersion@.
--
-- Note
--
-- Because Vulkan 1.0 implementations /may/ fail with
-- 'Vulkan.Core10.Enums.Result.ERROR_INCOMPATIBLE_DRIVER', applications
-- /should/ determine the version of Vulkan available before calling
-- 'createInstance'. If the 'getInstanceProcAddr' returns @NULL@ for
-- 'Vulkan.Core11.DeviceInitialization.enumerateInstanceVersion', it is a
-- Vulkan 1.0 implementation. Otherwise, the application /can/ call
-- 'Vulkan.Core11.DeviceInitialization.enumerateInstanceVersion' to
-- determine the version of Vulkan.
--
-- As long as the instance supports at least Vulkan 1.1, an application
-- /can/ use different versions of Vulkan with an instance than it does
-- with a device or physical device.
--
-- Note
--
-- The Khronos validation layers will treat @apiVersion@ as the highest API
-- version the application targets, and will validate API usage against the
-- minimum of that version and the implementation version (instance or
-- device, depending on context). If an application tries to use
-- functionality from a greater version than this, a validation error will
-- be triggered.
--
-- For example, if the instance supports Vulkan 1.1 and three physical
-- devices support Vulkan 1.0, Vulkan 1.1, and Vulkan 1.2, respectively,
-- and if the application sets @apiVersion@ to 1.2, the application /can/
-- use the following versions of Vulkan:
--
-- -   Vulkan 1.0 /can/ be used with the instance and with all physical
--     devices.
--
-- -   Vulkan 1.1 /can/ be used with the instance and with the physical
--     devices that support Vulkan 1.1 and Vulkan 1.2.
--
-- -   Vulkan 1.2 /can/ be used with the physical device that supports
--     Vulkan 1.2.
--
-- If we modify the above example so that the application sets @apiVersion@
-- to 1.1, then the application /must/ not use Vulkan 1.2 functionality on
-- the physical device that supports Vulkan 1.2.
--
-- Implicit layers /must/ be disabled if they do not support a version at
-- least as high as @apiVersion@. See the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#LoaderAndLayerInterface Vulkan Loader Specification and Architecture Overview>
-- document for additional information.
--
-- Note
--
-- Providing a @NULL@ 'InstanceCreateInfo'::@pApplicationInfo@ or providing
-- an @apiVersion@ of 0 is equivalent to providing an @apiVersion@ of
-- @VK_MAKE_VERSION(1,0,0)@.
--
-- == Valid Usage
--
-- -   If @apiVersion@ is not @0@, then it /must/ be greater or equal to
--     'Vulkan.Core10.API_VERSION_1_0'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_APPLICATION_INFO'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   If @pApplicationName@ is not @NULL@, @pApplicationName@ /must/ be a
--     null-terminated UTF-8 string
--
-- -   If @pEngineName@ is not @NULL@, @pEngineName@ /must/ be a
--     null-terminated UTF-8 string
--
-- = See Also
--
-- 'InstanceCreateInfo', 'Vulkan.Core10.Enums.StructureType.StructureType'
data ApplicationInfo = ApplicationInfo
  { -- | @pApplicationName@ is @NULL@ or is a pointer to a null-terminated UTF-8
    -- string containing the name of the application.
    ApplicationInfo -> Maybe ("name" ::: ByteString)
applicationName :: Maybe ByteString
  , -- | @applicationVersion@ is an unsigned integer variable containing the
    -- developer-supplied version number of the application.
    ApplicationInfo -> Word32
applicationVersion :: Word32
  , -- | @pEngineName@ is @NULL@ or is a pointer to a null-terminated UTF-8
    -- string containing the name of the engine (if any) used to create the
    -- application.
    ApplicationInfo -> Maybe ("name" ::: ByteString)
engineName :: Maybe ByteString
  , -- | @engineVersion@ is an unsigned integer variable containing the
    -- developer-supplied version number of the engine used to create the
    -- application.
    ApplicationInfo -> Word32
engineVersion :: Word32
  , -- | @apiVersion@ /must/ be the highest version of Vulkan that the
    -- application is designed to use, encoded as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-coreversions-versionnumbers>.
    -- The patch version number specified in @apiVersion@ is ignored when
    -- creating an instance object. Only the major and minor versions of the
    -- instance /must/ match those requested in @apiVersion@.
    ApplicationInfo -> Word32
apiVersion :: Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ApplicationInfo)
#endif
deriving instance Show ApplicationInfo

instance ToCStruct ApplicationInfo where
  withCStruct :: ApplicationInfo -> (Ptr ApplicationInfo -> IO b) -> IO b
withCStruct x :: ApplicationInfo
x f :: Ptr ApplicationInfo -> IO b
f = Int -> Int -> (Ptr ApplicationInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr ApplicationInfo -> IO b) -> IO b)
-> (Ptr ApplicationInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ApplicationInfo
p -> Ptr ApplicationInfo -> ApplicationInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ApplicationInfo
p ApplicationInfo
x (Ptr ApplicationInfo -> IO b
f Ptr ApplicationInfo
p)
  pokeCStruct :: Ptr ApplicationInfo -> ApplicationInfo -> IO b -> IO b
pokeCStruct p :: Ptr ApplicationInfo
p ApplicationInfo{..} 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 ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_APPLICATION_INFO)
    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 ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    "pName" ::: Ptr CChar
pApplicationName'' <- case (Maybe ("name" ::: ByteString)
applicationName) of
      Nothing -> ("pName" ::: Ptr CChar) -> ContT b IO ("pName" ::: Ptr CChar)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pName" ::: Ptr CChar
forall a. Ptr a
nullPtr
      Just j :: "name" ::: ByteString
j -> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
j)
    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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr CChar))) "pName" ::: Ptr CChar
pApplicationName''
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
applicationVersion)
    "pName" ::: Ptr CChar
pEngineName'' <- case (Maybe ("name" ::: ByteString)
engineName) of
      Nothing -> ("pName" ::: Ptr CChar) -> ContT b IO ("pName" ::: Ptr CChar)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pName" ::: Ptr CChar
forall a. Ptr a
nullPtr
      Just j :: "name" ::: ByteString
j -> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
j)
    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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar))) "pName" ::: Ptr CChar
pEngineName''
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
engineVersion)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
apiVersion)
    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 = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ApplicationInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr ApplicationInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_APPLICATION_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ApplicationInfo where
  peekCStruct :: Ptr ApplicationInfo -> IO ApplicationInfo
peekCStruct p :: Ptr ApplicationInfo
p = do
    "pName" ::: Ptr CChar
pApplicationName <- Ptr ("pName" ::: Ptr CChar) -> IO ("pName" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CChar) ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr CChar)))
    Maybe ("name" ::: ByteString)
pApplicationName' <- (("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString))
-> ("pName" ::: Ptr CChar) -> IO (Maybe ("name" ::: ByteString))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: "pName" ::: Ptr CChar
j -> ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
packCString  ("pName" ::: Ptr CChar
j)) "pName" ::: Ptr CChar
pApplicationName
    Word32
applicationVersion <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    "pName" ::: Ptr CChar
pEngineName <- Ptr ("pName" ::: Ptr CChar) -> IO ("pName" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CChar) ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar)))
    Maybe ("name" ::: ByteString)
pEngineName' <- (("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString))
-> ("pName" ::: Ptr CChar) -> IO (Maybe ("name" ::: ByteString))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: "pName" ::: Ptr CChar
j -> ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
packCString  ("pName" ::: Ptr CChar
j)) "pName" ::: Ptr CChar
pEngineName
    Word32
engineVersion <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    Word32
apiVersion <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ApplicationInfo
p Ptr ApplicationInfo -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32))
    ApplicationInfo -> IO ApplicationInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ApplicationInfo -> IO ApplicationInfo)
-> ApplicationInfo -> IO ApplicationInfo
forall a b. (a -> b) -> a -> b
$ Maybe ("name" ::: ByteString)
-> Word32
-> Maybe ("name" ::: ByteString)
-> Word32
-> Word32
-> ApplicationInfo
ApplicationInfo
             Maybe ("name" ::: ByteString)
pApplicationName' Word32
applicationVersion Maybe ("name" ::: ByteString)
pEngineName' Word32
engineVersion Word32
apiVersion

instance Zero ApplicationInfo where
  zero :: ApplicationInfo
zero = Maybe ("name" ::: ByteString)
-> Word32
-> Maybe ("name" ::: ByteString)
-> Word32
-> Word32
-> ApplicationInfo
ApplicationInfo
           Maybe ("name" ::: ByteString)
forall a. Maybe a
Nothing
           Word32
forall a. Zero a => a
zero
           Maybe ("name" ::: ByteString)
forall a. Maybe a
Nothing
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkInstanceCreateInfo - Structure specifying parameters of a newly
-- created instance
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_INSTANCE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_EXT_debug_report.DebugReportCallbackCreateInfoEXT',
--     'Vulkan.Extensions.VK_EXT_debug_utils.DebugUtilsMessengerCreateInfoEXT',
--     'Vulkan.Extensions.VK_EXT_validation_features.ValidationFeaturesEXT',
--     or 'Vulkan.Extensions.VK_EXT_validation_flags.ValidationFlagsEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   If @pApplicationInfo@ is not @NULL@, @pApplicationInfo@ /must/ be a
--     valid pointer to a valid 'ApplicationInfo' structure
--
-- -   If @enabledLayerCount@ is not @0@, @ppEnabledLayerNames@ /must/ be a
--     valid pointer to an array of @enabledLayerCount@ null-terminated
--     UTF-8 strings
--
-- -   If @enabledExtensionCount@ is not @0@, @ppEnabledExtensionNames@
--     /must/ be a valid pointer to an array of @enabledExtensionCount@
--     null-terminated UTF-8 strings
--
-- = See Also
--
-- 'ApplicationInfo',
-- 'Vulkan.Core10.Enums.InstanceCreateFlags.InstanceCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createInstance'
data InstanceCreateInfo (es :: [Type]) = InstanceCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    InstanceCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    InstanceCreateInfo es -> InstanceCreateFlags
flags :: InstanceCreateFlags
  , -- | @pApplicationInfo@ is @NULL@ or a pointer to a 'ApplicationInfo'
    -- structure. If not @NULL@, this information helps implementations
    -- recognize behavior inherent to classes of applications.
    -- 'ApplicationInfo' is defined in detail below.
    InstanceCreateInfo es -> Maybe ApplicationInfo
applicationInfo :: Maybe ApplicationInfo
  , -- | @ppEnabledLayerNames@ is a pointer to an array of @enabledLayerCount@
    -- null-terminated UTF-8 strings containing the names of layers to enable
    -- for the created instance. The layers are loaded in the order they are
    -- listed in this array, with the first array element being the closest to
    -- the application, and the last array element being the closest to the
    -- driver. See the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-layers>
    -- section for further details.
    InstanceCreateInfo es -> Vector ("name" ::: ByteString)
enabledLayerNames :: Vector ByteString
  , -- | @ppEnabledExtensionNames@ is a pointer to an array of
    -- @enabledExtensionCount@ null-terminated UTF-8 strings containing the
    -- names of extensions to enable.
    InstanceCreateInfo es -> Vector ("name" ::: ByteString)
enabledExtensionNames :: Vector ByteString
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (InstanceCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (InstanceCreateInfo es)

instance Extensible InstanceCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_INSTANCE_CREATE_INFO
  setNext :: InstanceCreateInfo ds -> Chain es -> InstanceCreateInfo es
setNext x :: InstanceCreateInfo ds
x next :: Chain es
next = InstanceCreateInfo ds
x{$sel:next:InstanceCreateInfo :: Chain es
next = Chain es
next}
  getNext :: InstanceCreateInfo es -> Chain es
getNext InstanceCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends InstanceCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends InstanceCreateInfo e => b) -> Maybe b
extends _ f :: Extends InstanceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DebugUtilsMessengerCreateInfoEXT) =>
Maybe (e :~: DebugUtilsMessengerCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DebugUtilsMessengerCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends InstanceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable ValidationFeaturesEXT) =>
Maybe (e :~: ValidationFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ValidationFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends InstanceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable ValidationFlagsEXT) =>
Maybe (e :~: ValidationFlagsEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ValidationFlagsEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends InstanceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DebugReportCallbackCreateInfoEXT) =>
Maybe (e :~: DebugReportCallbackCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DebugReportCallbackCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends InstanceCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss InstanceCreateInfo es, PokeChain es) => ToCStruct (InstanceCreateInfo es) where
  withCStruct :: InstanceCreateInfo es
-> (Ptr (InstanceCreateInfo es) -> IO b) -> IO b
withCStruct x :: InstanceCreateInfo es
x f :: Ptr (InstanceCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (InstanceCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (InstanceCreateInfo es) -> IO b) -> IO b)
-> (Ptr (InstanceCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (InstanceCreateInfo es)
p -> Ptr (InstanceCreateInfo es)
-> InstanceCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (InstanceCreateInfo es)
p InstanceCreateInfo es
x (Ptr (InstanceCreateInfo es) -> IO b
f Ptr (InstanceCreateInfo es)
p)
  pokeCStruct :: Ptr (InstanceCreateInfo es)
-> InstanceCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (InstanceCreateInfo es)
p InstanceCreateInfo{..} 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 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INSTANCE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    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 InstanceCreateFlags -> InstanceCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr InstanceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr InstanceCreateFlags)) (InstanceCreateFlags
flags)
    Ptr ApplicationInfo
pApplicationInfo'' <- case (Maybe ApplicationInfo
applicationInfo) of
      Nothing -> Ptr ApplicationInfo -> ContT b IO (Ptr ApplicationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ApplicationInfo
forall a. Ptr a
nullPtr
      Just j :: ApplicationInfo
j -> ((Ptr ApplicationInfo -> IO b) -> IO b)
-> ContT b IO (Ptr ApplicationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ApplicationInfo -> IO b) -> IO b)
 -> ContT b IO (Ptr ApplicationInfo))
-> ((Ptr ApplicationInfo -> IO b) -> IO b)
-> ContT b IO (Ptr ApplicationInfo)
forall a b. (a -> b) -> a -> b
$ ApplicationInfo -> (Ptr ApplicationInfo -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ApplicationInfo
j)
    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 ApplicationInfo) -> Ptr ApplicationInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr (Ptr ApplicationInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ApplicationInfo))) Ptr ApplicationInfo
pApplicationInfo''
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("name" ::: ByteString) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("name" ::: ByteString) -> Int)
-> Vector ("name" ::: ByteString) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("name" ::: ByteString)
enabledLayerNames)) :: Word32))
    Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames' <- ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("pName" ::: Ptr CChar)))
-> ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector ("name" ::: ByteString) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("name" ::: ByteString)
enabledLayerNames)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ("name" ::: ByteString) -> ContT b IO ())
-> Vector ("name" ::: ByteString) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "name" ::: ByteString
e -> do
      "pName" ::: Ptr CChar
ppEnabledLayerNames'' <- ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
e)
      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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames' Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) "pName" ::: Ptr CChar
ppEnabledLayerNames'') (Vector ("name" ::: ByteString)
enabledLayerNames)
    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 ("pName" ::: Ptr CChar))
-> Ptr ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar)))) (Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames')
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("name" ::: ByteString) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("name" ::: ByteString) -> Int)
-> Vector ("name" ::: ByteString) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("name" ::: ByteString)
enabledExtensionNames)) :: Word32))
    Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames' <- ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("pName" ::: Ptr CChar)))
-> ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector ("name" ::: ByteString) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("name" ::: ByteString)
enabledExtensionNames)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ("name" ::: ByteString) -> ContT b IO ())
-> Vector ("name" ::: ByteString) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "name" ::: ByteString
e -> do
      "pName" ::: Ptr CChar
ppEnabledExtensionNames'' <- ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
e)
      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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames' Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) "pName" ::: Ptr CChar
ppEnabledExtensionNames'') (Vector ("name" ::: ByteString)
enabledExtensionNames)
    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 ("pName" ::: Ptr CChar))
-> Ptr ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar)))) (Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames')
    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 = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (InstanceCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (InstanceCreateInfo es)
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 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INSTANCE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames' <- ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("pName" ::: Ptr CChar)))
-> ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ("name" ::: ByteString) -> ContT b IO ())
-> Vector ("name" ::: ByteString) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "name" ::: ByteString
e -> do
      "pName" ::: Ptr CChar
ppEnabledLayerNames'' <- ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
e)
      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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames' Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) "pName" ::: Ptr CChar
ppEnabledLayerNames'') (Vector ("name" ::: 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 (Ptr ("pName" ::: Ptr CChar))
-> Ptr ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar)))) (Ptr ("pName" ::: Ptr CChar)
pPpEnabledLayerNames')
    Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames' <- ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("pName" ::: Ptr CChar)))
-> ((Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr ("pName" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ("name" ::: ByteString) -> ContT b IO ())
-> Vector ("name" ::: ByteString) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "name" ::: ByteString
e -> do
      "pName" ::: Ptr CChar
ppEnabledExtensionNames'' <- ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pName" ::: Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO ("pName" ::: Ptr CChar))
-> ((("pName" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("pName" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO b) -> IO b
forall a.
("name" ::: ByteString)
-> (("pName" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("name" ::: ByteString
e)
      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 ("pName" ::: Ptr CChar) -> ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames' Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) "pName" ::: Ptr CChar
ppEnabledExtensionNames'') (Vector ("name" ::: 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 (Ptr ("pName" ::: Ptr CChar))
-> Ptr ("pName" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar)))) (Ptr ("pName" ::: Ptr CChar)
pPpEnabledExtensionNames')
    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 (Extendss InstanceCreateInfo es, PeekChain es) => FromCStruct (InstanceCreateInfo es) where
  peekCStruct :: Ptr (InstanceCreateInfo es) -> IO (InstanceCreateInfo es)
peekCStruct p :: Ptr (InstanceCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    InstanceCreateFlags
flags <- Ptr InstanceCreateFlags -> IO InstanceCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @InstanceCreateFlags ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr InstanceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr InstanceCreateFlags))
    Ptr ApplicationInfo
pApplicationInfo <- Ptr (Ptr ApplicationInfo) -> IO (Ptr ApplicationInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ApplicationInfo) ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es) -> Int -> Ptr (Ptr ApplicationInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ApplicationInfo)))
    Maybe ApplicationInfo
pApplicationInfo' <- (Ptr ApplicationInfo -> IO ApplicationInfo)
-> Ptr ApplicationInfo -> IO (Maybe ApplicationInfo)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr ApplicationInfo
j -> Ptr ApplicationInfo -> IO ApplicationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ApplicationInfo (Ptr ApplicationInfo
j)) Ptr ApplicationInfo
pApplicationInfo
    Word32
enabledLayerCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr ("pName" ::: Ptr CChar)
ppEnabledLayerNames <- Ptr (Ptr ("pName" ::: Ptr CChar))
-> IO (Ptr ("pName" ::: Ptr CChar))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (Ptr CChar)) ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar))))
    Vector ("name" ::: ByteString)
ppEnabledLayerNames' <- Int
-> (Int -> IO ("name" ::: ByteString))
-> IO (Vector ("name" ::: ByteString))
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
enabledLayerCount) (\i :: Int
i -> ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
packCString (("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString))
-> IO ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr ("pName" ::: Ptr CChar) -> IO ("pName" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek ((Ptr ("pName" ::: Ptr CChar)
ppEnabledLayerNames Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar))))
    Word32
enabledExtensionCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr ("pName" ::: Ptr CChar)
ppEnabledExtensionNames <- Ptr (Ptr ("pName" ::: Ptr CChar))
-> IO (Ptr ("pName" ::: Ptr CChar))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (Ptr CChar)) ((Ptr (InstanceCreateInfo es)
p Ptr (InstanceCreateInfo es)
-> Int -> Ptr (Ptr ("pName" ::: Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar))))
    Vector ("name" ::: ByteString)
ppEnabledExtensionNames' <- Int
-> (Int -> IO ("name" ::: ByteString))
-> IO (Vector ("name" ::: ByteString))
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
enabledExtensionCount) (\i :: Int
i -> ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
packCString (("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString))
-> IO ("pName" ::: Ptr CChar) -> IO ("name" ::: ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr ("pName" ::: Ptr CChar) -> IO ("pName" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek ((Ptr ("pName" ::: Ptr CChar)
ppEnabledExtensionNames Ptr ("pName" ::: Ptr CChar) -> Int -> Ptr ("pName" ::: Ptr CChar)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar))))
    InstanceCreateInfo es -> IO (InstanceCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InstanceCreateInfo es -> IO (InstanceCreateInfo es))
-> InstanceCreateInfo es -> IO (InstanceCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> InstanceCreateFlags
-> Maybe ApplicationInfo
-> Vector ("name" ::: ByteString)
-> Vector ("name" ::: ByteString)
-> InstanceCreateInfo es
forall (es :: [*]).
Chain es
-> InstanceCreateFlags
-> Maybe ApplicationInfo
-> Vector ("name" ::: ByteString)
-> Vector ("name" ::: ByteString)
-> InstanceCreateInfo es
InstanceCreateInfo
             Chain es
next InstanceCreateFlags
flags Maybe ApplicationInfo
pApplicationInfo' Vector ("name" ::: ByteString)
ppEnabledLayerNames' Vector ("name" ::: ByteString)
ppEnabledExtensionNames'

instance es ~ '[] => Zero (InstanceCreateInfo es) where
  zero :: InstanceCreateInfo es
zero = Chain es
-> InstanceCreateFlags
-> Maybe ApplicationInfo
-> Vector ("name" ::: ByteString)
-> Vector ("name" ::: ByteString)
-> InstanceCreateInfo es
forall (es :: [*]).
Chain es
-> InstanceCreateFlags
-> Maybe ApplicationInfo
-> Vector ("name" ::: ByteString)
-> Vector ("name" ::: ByteString)
-> InstanceCreateInfo es
InstanceCreateInfo
           ()
           InstanceCreateFlags
forall a. Zero a => a
zero
           Maybe ApplicationInfo
forall a. Maybe a
Nothing
           Vector ("name" ::: ByteString)
forall a. Monoid a => a
mempty
           Vector ("name" ::: ByteString)
forall a. Monoid a => a
mempty


-- | VkQueueFamilyProperties - Structure providing information about a queue
-- family
--
-- = Description
--
-- The value returned in @minImageTransferGranularity@ has a unit of
-- compressed texel blocks for images having a block-compressed format, and
-- a unit of texels otherwise.
--
-- Possible values of @minImageTransferGranularity@ are:
--
-- -   (0,0,0) which indicates that only whole mip levels /must/ be
--     transferred using the image transfer operations on the corresponding
--     queues. In this case, the following restrictions apply to all offset
--     and extent parameters of image transfer operations:
--
--     -   The @x@, @y@, and @z@ members of a
--         'Vulkan.Core10.FundamentalTypes.Offset3D' parameter /must/
--         always be zero.
--
--     -   The @width@, @height@, and @depth@ members of a
--         'Vulkan.Core10.FundamentalTypes.Extent3D' parameter /must/
--         always match the width, height, and depth of the image
--         subresource corresponding to the parameter, respectively.
--
-- -   (Ax, Ay, Az) where Ax, Ay, and Az are all integer powers of two. In
--     this case the following restrictions apply to all image transfer
--     operations:
--
--     -   @x@, @y@, and @z@ of a 'Vulkan.Core10.FundamentalTypes.Offset3D'
--         parameter /must/ be integer multiples of Ax, Ay, and Az,
--         respectively.
--
--     -   @width@ of a 'Vulkan.Core10.FundamentalTypes.Extent3D' parameter
--         /must/ be an integer multiple of Ax, or else @x@ + @width@
--         /must/ equal the width of the image subresource corresponding to
--         the parameter.
--
--     -   @height@ of a 'Vulkan.Core10.FundamentalTypes.Extent3D'
--         parameter /must/ be an integer multiple of Ay, or else @y@ +
--         @height@ /must/ equal the height of the image subresource
--         corresponding to the parameter.
--
--     -   @depth@ of a 'Vulkan.Core10.FundamentalTypes.Extent3D' parameter
--         /must/ be an integer multiple of Az, or else @z@ + @depth@
--         /must/ equal the depth of the image subresource corresponding to
--         the parameter.
--
--     -   If the format of the image corresponding to the parameters is
--         one of the block-compressed formats then for the purposes of the
--         above calculations the granularity /must/ be scaled up by the
--         compressed texel block dimensions.
--
-- Queues supporting graphics and\/or compute operations /must/ report
-- (1,1,1) in @minImageTransferGranularity@, meaning that there are no
-- additional restrictions on the granularity of image transfer operations
-- for these queues. Other queues supporting image transfer operations are
-- only /required/ to support whole mip level transfers, thus
-- @minImageTransferGranularity@ for queues belonging to such queue
-- families /may/ be (0,0,0).
--
-- The
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-device Device Memory>
-- section describes memory properties queried from the physical device.
--
-- For physical device feature queries see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features Features>
-- chapter.
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Extent3D',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.QueueFamilyProperties2',
-- 'Vulkan.Core10.Enums.QueueFlagBits.QueueFlags',
-- 'getPhysicalDeviceQueueFamilyProperties'
data QueueFamilyProperties = QueueFamilyProperties
  { -- | @queueFlags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QueueFlagBits' indicating
    -- capabilities of the queues in this queue family.
    QueueFamilyProperties -> QueueFlags
queueFlags :: QueueFlags
  , -- | @queueCount@ is the unsigned integer count of queues in this queue
    -- family. Each queue family /must/ support at least one queue.
    QueueFamilyProperties -> Word32
queueCount :: Word32
  , -- | @timestampValidBits@ is the unsigned integer count of meaningful bits in
    -- the timestamps written via
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp'. The valid range
    -- for the count is 36..64 bits, or a value of 0, indicating no support for
    -- timestamps. Bits outside the valid range are guaranteed to be zeros.
    QueueFamilyProperties -> Word32
timestampValidBits :: Word32
  , -- | @minImageTransferGranularity@ is the minimum granularity supported for
    -- image transfer operations on the queues in this queue family.
    QueueFamilyProperties -> Extent3D
minImageTransferGranularity :: Extent3D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueueFamilyProperties)
#endif
deriving instance Show QueueFamilyProperties

instance ToCStruct QueueFamilyProperties where
  withCStruct :: QueueFamilyProperties
-> (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
    -> IO b)
-> IO b
withCStruct x :: QueueFamilyProperties
x f :: ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties) -> IO b
f = Int
-> Int
-> (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 4 ((("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties) -> IO b)
 -> IO b)
-> (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p -> ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> QueueFamilyProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p QueueFamilyProperties
x (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties) -> IO b
f "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p)
  pokeCStruct :: ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> QueueFamilyProperties -> IO b -> IO b
pokeCStruct p :: "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p QueueFamilyProperties{..} 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 QueueFlags -> QueueFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> Ptr QueueFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr QueueFlags)) (QueueFlags
queueFlags)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
queueCount)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
timestampValidBits)
    ((() -> 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Extent3D)) (Extent3D
minImageTransferGranularity) (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 = 24
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO b -> IO b
pokeZeroCStruct p :: "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Extent3D)) (Extent3D
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 QueueFamilyProperties where
  peekCStruct :: ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> IO QueueFamilyProperties
peekCStruct p :: "pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p = do
    QueueFlags
queueFlags <- Ptr QueueFlags -> IO QueueFlags
forall a. Storable a => Ptr a -> IO a
peek @QueueFlags (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> Ptr QueueFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr QueueFlags))
    Word32
queueCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
timestampValidBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Extent3D
minImageTransferGranularity <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties
p ("pQueueFamilyProperties" ::: Ptr QueueFamilyProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Extent3D))
    QueueFamilyProperties -> IO QueueFamilyProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueueFamilyProperties -> IO QueueFamilyProperties)
-> QueueFamilyProperties -> IO QueueFamilyProperties
forall a b. (a -> b) -> a -> b
$ QueueFlags -> Word32 -> Word32 -> Extent3D -> QueueFamilyProperties
QueueFamilyProperties
             QueueFlags
queueFlags Word32
queueCount Word32
timestampValidBits Extent3D
minImageTransferGranularity

instance Zero QueueFamilyProperties where
  zero :: QueueFamilyProperties
zero = QueueFlags -> Word32 -> Word32 -> Extent3D -> QueueFamilyProperties
QueueFamilyProperties
           QueueFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Extent3D
forall a. Zero a => a
zero


-- | VkPhysicalDeviceMemoryProperties - Structure specifying physical device
-- memory properties
--
-- = Description
--
-- The 'PhysicalDeviceMemoryProperties' structure describes a number of
-- /memory heaps/ as well as a number of /memory types/ that /can/ be used
-- to access memory allocated in those heaps. Each heap describes a memory
-- resource of a particular size, and each memory type describes a set of
-- memory properties (e.g. host cached vs uncached) that /can/ be used with
-- a given memory heap. Allocations using a particular memory type will
-- consume resources from the heap indicated by that memory type’s heap
-- index. More than one memory type /may/ share each heap, and the heaps
-- and memory types provide a mechanism to advertise an accurate size of
-- the physical memory resources while allowing the memory to be used with
-- a variety of different properties.
--
-- The number of memory heaps is given by @memoryHeapCount@ and is less
-- than or equal to 'Vulkan.Core10.APIConstants.MAX_MEMORY_HEAPS'. Each
-- heap is described by an element of the @memoryHeaps@ array as a
-- 'MemoryHeap' structure. The number of memory types available across all
-- memory heaps is given by @memoryTypeCount@ and is less than or equal to
-- 'Vulkan.Core10.APIConstants.MAX_MEMORY_TYPES'. Each memory type is
-- described by an element of the @memoryTypes@ array as a 'MemoryType'
-- structure.
--
-- At least one heap /must/ include
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_DEVICE_LOCAL_BIT' in
-- 'MemoryHeap'::@flags@. If there are multiple heaps that all have similar
-- performance characteristics, they /may/ all include
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_DEVICE_LOCAL_BIT'.
-- In a unified memory architecture (UMA) system there is often only a
-- single memory heap which is considered to be equally “local” to the host
-- and to the device, and such an implementation /must/ advertise the heap
-- as device-local.
--
-- Each memory type returned by 'getPhysicalDeviceMemoryProperties' /must/
-- have its @propertyFlags@ set to one of the following values:
--
-- -   0
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--
-- -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_CACHED_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     |
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--
-- There /must/ be at least one memory type with both the
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
-- and
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT'
-- bits set in its @propertyFlags@. There /must/ be at least one memory
-- type with the
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
-- bit set in its @propertyFlags@. If the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-deviceCoherentMemory deviceCoherentMemory>
-- feature is enabled, there /must/ be at least one memory type with the
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
-- bit set in its @propertyFlags@.
--
-- For each pair of elements __X__ and __Y__ returned in @memoryTypes@,
-- __X__ /must/ be placed at a lower index position than __Y__ if:
--
-- -   the set of bit flags returned in the @propertyFlags@ member of __X__
--     is a strict subset of the set of bit flags returned in the
--     @propertyFlags@ member of __Y__; or
--
-- -   the @propertyFlags@ members of __X__ and __Y__ are equal, and __X__
--     belongs to a memory heap with greater performance (as determined in
--     an implementation-specific manner) ; or
--
-- -   the @propertyFlags@ members of __Y__ includes
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD'
--     or
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD'
--     and __X__ does not
--
-- Note
--
-- There is no ordering requirement between __X__ and __Y__ elements for
-- the case their @propertyFlags@ members are not in a subset relation.
-- That potentially allows more than one possible way to order the same set
-- of memory types. Notice that the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-device-bitmask-list list of all allowed memory property flag combinations>
-- is written in a valid order. But if instead
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_LOCAL_BIT'
-- was before
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
-- |
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT',
-- the list would still be in a valid order.
--
-- There may be a performance penalty for using device coherent or uncached
-- device memory types, and using these accidentally is undesirable. In
-- order to avoid this, memory types with these properties always appear at
-- the end of the list; but are subject to the same rules otherwise.
--
-- This ordering requirement enables applications to use a simple search
-- loop to select the desired memory type along the lines of:
--
-- > // Find a memory in `memoryTypeBitsRequirement` that includes all of `requiredProperties`
-- > int32_t findProperties(const VkPhysicalDeviceMemoryProperties* pMemoryProperties,
-- >                        uint32_t memoryTypeBitsRequirement,
-- >                        VkMemoryPropertyFlags requiredProperties) {
-- >     const uint32_t memoryCount = pMemoryProperties->memoryTypeCount;
-- >     for (uint32_t memoryIndex = 0; memoryIndex < memoryCount; ++memoryIndex) {
-- >         const uint32_t memoryTypeBits = (1 << memoryIndex);
-- >         const bool isRequiredMemoryType = memoryTypeBitsRequirement & memoryTypeBits;
-- >
-- >         const VkMemoryPropertyFlags properties =
-- >             pMemoryProperties->memoryTypes[memoryIndex].propertyFlags;
-- >         const bool hasRequiredProperties =
-- >             (properties & requiredProperties) == requiredProperties;
-- >
-- >         if (isRequiredMemoryType && hasRequiredProperties)
-- >             return static_cast<int32_t>(memoryIndex);
-- >     }
-- >
-- >     // failed to find memory type
-- >     return -1;
-- > }
-- >
-- > // Try to find an optimal memory type, or if it does not exist try fallback memory type
-- > // `device` is the VkDevice
-- > // `image` is the VkImage that requires memory to be bound
-- > // `memoryProperties` properties as returned by vkGetPhysicalDeviceMemoryProperties
-- > // `requiredProperties` are the property flags that must be present
-- > // `optimalProperties` are the property flags that are preferred by the application
-- > VkMemoryRequirements memoryRequirements;
-- > vkGetImageMemoryRequirements(device, image, &memoryRequirements);
-- > int32_t memoryType =
-- >     findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, optimalProperties);
-- > if (memoryType == -1) // not found; try fallback properties
-- >     memoryType =
-- >         findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, requiredProperties);
--
-- = See Also
--
-- 'MemoryHeap', 'MemoryType',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceMemoryProperties2',
-- 'getPhysicalDeviceMemoryProperties'
data PhysicalDeviceMemoryProperties = PhysicalDeviceMemoryProperties
  { -- | @memoryTypeCount@ is the number of valid elements in the @memoryTypes@
    -- array.
    PhysicalDeviceMemoryProperties -> Word32
memoryTypeCount :: Word32
  , -- | @memoryTypes@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_MEMORY_TYPES' 'MemoryType' structures
    -- describing the /memory types/ that /can/ be used to access memory
    -- allocated from the heaps specified by @memoryHeaps@.
    PhysicalDeviceMemoryProperties -> Vector MemoryType
memoryTypes :: Vector MemoryType
  , -- | @memoryHeapCount@ is the number of valid elements in the @memoryHeaps@
    -- array.
    PhysicalDeviceMemoryProperties -> Word32
memoryHeapCount :: Word32
  , -- | @memoryHeaps@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_MEMORY_HEAPS' 'MemoryHeap' structures
    -- describing the /memory heaps/ from which memory /can/ be allocated.
    PhysicalDeviceMemoryProperties -> Vector MemoryHeap
memoryHeaps :: Vector MemoryHeap
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMemoryProperties)
#endif
deriving instance Show PhysicalDeviceMemoryProperties

instance ToCStruct PhysicalDeviceMemoryProperties where
  withCStruct :: PhysicalDeviceMemoryProperties
-> (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
    -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceMemoryProperties
x f :: ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO b
f = Int
-> Int
-> (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 520 8 ((("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
  -> IO b)
 -> IO b)
-> (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> PhysicalDeviceMemoryProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p PhysicalDeviceMemoryProperties
x (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO b
f "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p)
  pokeCStruct :: ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> PhysicalDeviceMemoryProperties -> IO b -> IO b
pokeCStruct p :: "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p PhysicalDeviceMemoryProperties{..} 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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
memoryTypeCount)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector MemoryType -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MemoryType -> Int) -> Vector MemoryType -> Int
forall a b. (a -> b) -> a -> b
$ (Vector MemoryType
memoryTypes)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (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 "" "memoryTypes is too long, a maximum of MAX_MEMORY_TYPES elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> MemoryType -> ContT b IO ())
-> Vector MemoryType -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryType
e -> ((() -> 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 MemoryType -> MemoryType -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FixedArray MAX_MEMORY_TYPES MemoryType) -> Ptr MemoryType
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)))) Ptr MemoryType -> Int -> Ptr MemoryType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryType) (MemoryType
e) (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
$ ())) (Vector MemoryType
memoryTypes)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32)) (Word32
memoryHeapCount)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector MemoryHeap -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MemoryHeap -> Int) -> Vector MemoryHeap -> Int
forall a b. (a -> b) -> a -> b
$ (Vector MemoryHeap
memoryHeaps)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (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 "" "memoryHeaps is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> MemoryHeap -> ContT b IO ())
-> Vector MemoryHeap -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryHeap
e -> ((() -> 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 MemoryHeap -> MemoryHeap -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FixedArray UUID_SIZE MemoryHeap) -> Ptr MemoryHeap
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray UUID_SIZE MemoryHeap)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr (FixedArray MAX_MEMORY_HEAPS MemoryHeap)))) Ptr MemoryHeap -> Int -> Ptr MemoryHeap
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryHeap) (MemoryHeap
e) (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
$ ())) (Vector MemoryHeap
memoryHeaps)
    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 = 520
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO b -> IO b
pokeZeroCStruct p :: "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (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 "" "memoryTypes is too long, a maximum of MAX_MEMORY_TYPES elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> MemoryType -> ContT b IO ())
-> Vector MemoryType -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryType
e -> ((() -> 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 MemoryType -> MemoryType -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FixedArray MAX_MEMORY_TYPES MemoryType) -> Ptr MemoryType
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)))) Ptr MemoryType -> Int -> Ptr MemoryType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryType) (MemoryType
e) (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
$ ())) (Vector MemoryType
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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (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 "" "memoryHeaps is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> MemoryHeap -> ContT b IO ())
-> Vector MemoryHeap -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MemoryHeap
e -> ((() -> 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 MemoryHeap -> MemoryHeap -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FixedArray UUID_SIZE MemoryHeap) -> Ptr MemoryHeap
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray UUID_SIZE MemoryHeap)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr (FixedArray MAX_MEMORY_HEAPS MemoryHeap)))) Ptr MemoryHeap -> Int -> Ptr MemoryHeap
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryHeap) (MemoryHeap
e) (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
$ ())) (Vector MemoryHeap
forall a. Monoid a => a
mempty)
    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 PhysicalDeviceMemoryProperties where
  peekCStruct :: ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> IO PhysicalDeviceMemoryProperties
peekCStruct p :: "pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p = do
    Word32
memoryTypeCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Vector MemoryType
memoryTypes <- Int -> (Int -> IO MemoryType) -> IO (Vector MemoryType)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (\i :: Int
i -> Ptr MemoryType -> IO MemoryType
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @MemoryType (((Ptr (FixedArray MAX_MEMORY_TYPES MemoryType) -> Ptr MemoryType
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @MemoryType (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr (FixedArray MAX_MEMORY_TYPES MemoryType)))) Ptr MemoryType -> Int -> Ptr MemoryType
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryType)))
    Word32
memoryHeapCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32))
    Vector MemoryHeap
memoryHeaps <- Int -> (Int -> IO MemoryHeap) -> IO (Vector MemoryHeap)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (\i :: Int
i -> Ptr MemoryHeap -> IO MemoryHeap
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @MemoryHeap (((Ptr (FixedArray UUID_SIZE MemoryHeap) -> Ptr MemoryHeap
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @MemoryHeap (("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties
p ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties)
-> Int -> Ptr (FixedArray UUID_SIZE MemoryHeap)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr (FixedArray MAX_MEMORY_HEAPS MemoryHeap)))) Ptr MemoryHeap -> Int -> Ptr MemoryHeap
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryHeap)))
    PhysicalDeviceMemoryProperties -> IO PhysicalDeviceMemoryProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryProperties
 -> IO PhysicalDeviceMemoryProperties)
-> PhysicalDeviceMemoryProperties
-> IO PhysicalDeviceMemoryProperties
forall a b. (a -> b) -> a -> b
$ Word32
-> Vector MemoryType
-> Word32
-> Vector MemoryHeap
-> PhysicalDeviceMemoryProperties
PhysicalDeviceMemoryProperties
             Word32
memoryTypeCount Vector MemoryType
memoryTypes Word32
memoryHeapCount Vector MemoryHeap
memoryHeaps

instance Zero PhysicalDeviceMemoryProperties where
  zero :: PhysicalDeviceMemoryProperties
zero = Word32
-> Vector MemoryType
-> Word32
-> Vector MemoryHeap
-> PhysicalDeviceMemoryProperties
PhysicalDeviceMemoryProperties
           Word32
forall a. Zero a => a
zero
           Vector MemoryType
forall a. Monoid a => a
mempty
           Word32
forall a. Zero a => a
zero
           Vector MemoryHeap
forall a. Monoid a => a
mempty


-- | VkMemoryType - Structure specifying memory type
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MemoryPropertyFlags',
-- 'PhysicalDeviceMemoryProperties'
data MemoryType = MemoryType
  { -- | @propertyFlags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MemoryPropertyFlagBits' of
    -- properties for this memory type.
    MemoryType -> MemoryPropertyFlags
propertyFlags :: MemoryPropertyFlags
  , -- | @heapIndex@ describes which memory heap this memory type corresponds to,
    -- and /must/ be less than @memoryHeapCount@ from the
    -- 'PhysicalDeviceMemoryProperties' structure.
    MemoryType -> Word32
heapIndex :: Word32
  }
  deriving (Typeable, MemoryType -> MemoryType -> Bool
(MemoryType -> MemoryType -> Bool)
-> (MemoryType -> MemoryType -> Bool) -> Eq MemoryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryType -> MemoryType -> Bool
$c/= :: MemoryType -> MemoryType -> Bool
== :: MemoryType -> MemoryType -> Bool
$c== :: MemoryType -> MemoryType -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryType)
#endif
deriving instance Show MemoryType

instance ToCStruct MemoryType where
  withCStruct :: MemoryType -> (Ptr MemoryType -> IO b) -> IO b
withCStruct x :: MemoryType
x f :: Ptr MemoryType -> IO b
f = Int -> Int -> (Ptr MemoryType -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr MemoryType -> IO b) -> IO b)
-> (Ptr MemoryType -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryType
p -> Ptr MemoryType -> MemoryType -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryType
p MemoryType
x (Ptr MemoryType -> IO b
f Ptr MemoryType
p)
  pokeCStruct :: Ptr MemoryType -> MemoryType -> IO b -> IO b
pokeCStruct p :: Ptr MemoryType
p MemoryType{..} f :: IO b
f = do
    Ptr MemoryPropertyFlags -> MemoryPropertyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryType
p Ptr MemoryType -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr MemoryPropertyFlags)) (MemoryPropertyFlags
propertyFlags)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryType
p Ptr MemoryType -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
heapIndex)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr MemoryType -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryType
p f :: IO b
f = do
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryType
p Ptr MemoryType -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryType where
  peekCStruct :: Ptr MemoryType -> IO MemoryType
peekCStruct p :: Ptr MemoryType
p = do
    MemoryPropertyFlags
propertyFlags <- Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryPropertyFlags ((Ptr MemoryType
p Ptr MemoryType -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr MemoryPropertyFlags))
    Word32
heapIndex <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MemoryType
p Ptr MemoryType -> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    MemoryType -> IO MemoryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryType -> IO MemoryType) -> MemoryType -> IO MemoryType
forall a b. (a -> b) -> a -> b
$ MemoryPropertyFlags -> Word32 -> MemoryType
MemoryType
             MemoryPropertyFlags
propertyFlags Word32
heapIndex

instance Storable MemoryType where
  sizeOf :: MemoryType -> Int
sizeOf ~MemoryType
_ = 8
  alignment :: MemoryType -> Int
alignment ~MemoryType
_ = 4
  peek :: Ptr MemoryType -> IO MemoryType
peek = Ptr MemoryType -> IO MemoryType
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryType -> MemoryType -> IO ()
poke ptr :: Ptr MemoryType
ptr poked :: MemoryType
poked = Ptr MemoryType -> MemoryType -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryType
ptr MemoryType
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryType where
  zero :: MemoryType
zero = MemoryPropertyFlags -> Word32 -> MemoryType
MemoryType
           MemoryPropertyFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkMemoryHeap - Structure specifying a memory heap
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MemoryHeapFlags',
-- 'PhysicalDeviceMemoryProperties'
data MemoryHeap = MemoryHeap
  { -- | @size@ is the total memory size in bytes in the heap.
    MemoryHeap -> DeviceSize
size :: DeviceSize
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MemoryHeapFlagBits' specifying
    -- attribute flags for the heap.
    MemoryHeap -> MemoryHeapFlags
flags :: MemoryHeapFlags
  }
  deriving (Typeable, MemoryHeap -> MemoryHeap -> Bool
(MemoryHeap -> MemoryHeap -> Bool)
-> (MemoryHeap -> MemoryHeap -> Bool) -> Eq MemoryHeap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryHeap -> MemoryHeap -> Bool
$c/= :: MemoryHeap -> MemoryHeap -> Bool
== :: MemoryHeap -> MemoryHeap -> Bool
$c== :: MemoryHeap -> MemoryHeap -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryHeap)
#endif
deriving instance Show MemoryHeap

instance ToCStruct MemoryHeap where
  withCStruct :: MemoryHeap -> (Ptr MemoryHeap -> IO b) -> IO b
withCStruct x :: MemoryHeap
x f :: Ptr MemoryHeap -> IO b
f = Int -> Int -> (Ptr MemoryHeap -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((Ptr MemoryHeap -> IO b) -> IO b)
-> (Ptr MemoryHeap -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryHeap
p -> Ptr MemoryHeap -> MemoryHeap -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryHeap
p MemoryHeap
x (Ptr MemoryHeap -> IO b
f Ptr MemoryHeap
p)
  pokeCStruct :: Ptr MemoryHeap -> MemoryHeap -> IO b -> IO b
pokeCStruct p :: Ptr MemoryHeap
p MemoryHeap{..} f :: IO b
f = do
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryHeap
p Ptr MemoryHeap -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
size)
    Ptr MemoryHeapFlags -> MemoryHeapFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryHeap
p Ptr MemoryHeap -> Int -> Ptr MemoryHeapFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr MemoryHeapFlags)) (MemoryHeapFlags
flags)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr MemoryHeap -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryHeap
p f :: IO b
f = do
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryHeap
p Ptr MemoryHeap -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryHeap where
  peekCStruct :: Ptr MemoryHeap -> IO MemoryHeap
peekCStruct p :: Ptr MemoryHeap
p = do
    DeviceSize
size <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr MemoryHeap
p Ptr MemoryHeap -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
    MemoryHeapFlags
flags <- Ptr MemoryHeapFlags -> IO MemoryHeapFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryHeapFlags ((Ptr MemoryHeap
p Ptr MemoryHeap -> Int -> Ptr MemoryHeapFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr MemoryHeapFlags))
    MemoryHeap -> IO MemoryHeap
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryHeap -> IO MemoryHeap) -> MemoryHeap -> IO MemoryHeap
forall a b. (a -> b) -> a -> b
$ DeviceSize -> MemoryHeapFlags -> MemoryHeap
MemoryHeap
             DeviceSize
size MemoryHeapFlags
flags

instance Storable MemoryHeap where
  sizeOf :: MemoryHeap -> Int
sizeOf ~MemoryHeap
_ = 16
  alignment :: MemoryHeap -> Int
alignment ~MemoryHeap
_ = 8
  peek :: Ptr MemoryHeap -> IO MemoryHeap
peek = Ptr MemoryHeap -> IO MemoryHeap
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryHeap -> MemoryHeap -> IO ()
poke ptr :: Ptr MemoryHeap
ptr poked :: MemoryHeap
poked = Ptr MemoryHeap -> MemoryHeap -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryHeap
ptr MemoryHeap
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryHeap where
  zero :: MemoryHeap
zero = DeviceSize -> MemoryHeapFlags -> MemoryHeap
MemoryHeap
           DeviceSize
forall a. Zero a => a
zero
           MemoryHeapFlags
forall a. Zero a => a
zero


-- | VkFormatProperties - Structure specifying image format properties
--
-- = Description
--
-- Note
--
-- If no format feature flags are supported, the format itself is not
-- supported, and images of that format cannot be created.
--
-- If @format@ is a block-compressed format, then @bufferFeatures@ /must/
-- not support any features for the format.
--
-- If @format@ is not a multi-plane format then @linearTilingFeatures@ and
-- @optimalTilingFeatures@ /must/ not contain
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DISJOINT_BIT'.
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlags',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.FormatProperties2',
-- 'getPhysicalDeviceFormatProperties'
data FormatProperties = FormatProperties
  { -- | @linearTilingFeatures@ is a bitmask of
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlagBits'
    -- specifying features supported by images created with a @tiling@
    -- parameter of 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR'.
    FormatProperties -> FormatFeatureFlags
linearTilingFeatures :: FormatFeatureFlags
  , -- | @optimalTilingFeatures@ is a bitmask of
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlagBits'
    -- specifying features supported by images created with a @tiling@
    -- parameter of 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL'.
    FormatProperties -> FormatFeatureFlags
optimalTilingFeatures :: FormatFeatureFlags
  , -- | @bufferFeatures@ is a bitmask of
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlagBits'
    -- specifying features supported by buffers.
    FormatProperties -> FormatFeatureFlags
bufferFeatures :: FormatFeatureFlags
  }
  deriving (Typeable, FormatProperties -> FormatProperties -> Bool
(FormatProperties -> FormatProperties -> Bool)
-> (FormatProperties -> FormatProperties -> Bool)
-> Eq FormatProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatProperties -> FormatProperties -> Bool
$c/= :: FormatProperties -> FormatProperties -> Bool
== :: FormatProperties -> FormatProperties -> Bool
$c== :: FormatProperties -> FormatProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FormatProperties)
#endif
deriving instance Show FormatProperties

instance ToCStruct FormatProperties where
  withCStruct :: FormatProperties
-> (("pFormatProperties" ::: Ptr FormatProperties) -> IO b) -> IO b
withCStruct x :: FormatProperties
x f :: ("pFormatProperties" ::: Ptr FormatProperties) -> IO b
f = Int
-> Int
-> (("pFormatProperties" ::: Ptr FormatProperties) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((("pFormatProperties" ::: Ptr FormatProperties) -> IO b) -> IO b)
-> (("pFormatProperties" ::: Ptr FormatProperties) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pFormatProperties" ::: Ptr FormatProperties
p -> ("pFormatProperties" ::: Ptr FormatProperties)
-> FormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pFormatProperties" ::: Ptr FormatProperties
p FormatProperties
x (("pFormatProperties" ::: Ptr FormatProperties) -> IO b
f "pFormatProperties" ::: Ptr FormatProperties
p)
  pokeCStruct :: ("pFormatProperties" ::: Ptr FormatProperties)
-> FormatProperties -> IO b -> IO b
pokeCStruct p :: "pFormatProperties" ::: Ptr FormatProperties
p FormatProperties{..} f :: IO b
f = do
    Ptr FormatFeatureFlags -> FormatFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
linearTilingFeatures)
    Ptr FormatFeatureFlags -> FormatFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
optimalTilingFeatures)
    Ptr FormatFeatureFlags -> FormatFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
bufferFeatures)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pFormatProperties" ::: Ptr FormatProperties) -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f

instance FromCStruct FormatProperties where
  peekCStruct :: ("pFormatProperties" ::: Ptr FormatProperties)
-> IO FormatProperties
peekCStruct p :: "pFormatProperties" ::: Ptr FormatProperties
p = do
    FormatFeatureFlags
linearTilingFeatures <- Ptr FormatFeatureFlags -> IO FormatFeatureFlags
forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr FormatFeatureFlags))
    FormatFeatureFlags
optimalTilingFeatures <- Ptr FormatFeatureFlags -> IO FormatFeatureFlags
forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr FormatFeatureFlags))
    FormatFeatureFlags
bufferFeatures <- Ptr FormatFeatureFlags -> IO FormatFeatureFlags
forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags (("pFormatProperties" ::: Ptr FormatProperties
p ("pFormatProperties" ::: Ptr FormatProperties)
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr FormatFeatureFlags))
    FormatProperties -> IO FormatProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FormatProperties -> IO FormatProperties)
-> FormatProperties -> IO FormatProperties
forall a b. (a -> b) -> a -> b
$ FormatFeatureFlags
-> FormatFeatureFlags -> FormatFeatureFlags -> FormatProperties
FormatProperties
             FormatFeatureFlags
linearTilingFeatures FormatFeatureFlags
optimalTilingFeatures FormatFeatureFlags
bufferFeatures

instance Storable FormatProperties where
  sizeOf :: FormatProperties -> Int
sizeOf ~FormatProperties
_ = 12
  alignment :: FormatProperties -> Int
alignment ~FormatProperties
_ = 4
  peek :: ("pFormatProperties" ::: Ptr FormatProperties)
-> IO FormatProperties
peek = ("pFormatProperties" ::: Ptr FormatProperties)
-> IO FormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pFormatProperties" ::: Ptr FormatProperties)
-> FormatProperties -> IO ()
poke ptr :: "pFormatProperties" ::: Ptr FormatProperties
ptr poked :: FormatProperties
poked = ("pFormatProperties" ::: Ptr FormatProperties)
-> FormatProperties -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pFormatProperties" ::: Ptr FormatProperties
ptr FormatProperties
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero FormatProperties where
  zero :: FormatProperties
zero = FormatFeatureFlags
-> FormatFeatureFlags -> FormatFeatureFlags -> FormatProperties
FormatProperties
           FormatFeatureFlags
forall a. Zero a => a
zero
           FormatFeatureFlags
forall a. Zero a => a
zero
           FormatFeatureFlags
forall a. Zero a => a
zero


-- | VkImageFormatProperties - Structure specifying an image format
-- properties
--
-- = Members
--
-- -   @maxExtent@ are the maximum image dimensions. See the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extentperimagetype Allowed Extent Values>
--     section below for how these values are constrained by @type@.
--
-- -   @maxMipLevels@ is the maximum number of mipmap levels.
--     @maxMipLevels@ /must/ be equal to the number of levels in the
--     complete mipmap chain based on the @maxExtent.width@,
--     @maxExtent.height@, and @maxExtent.depth@, except when one of the
--     following conditions is true, in which case it /may/ instead be @1@:
--
--     -   'getPhysicalDeviceImageFormatProperties'::@tiling@ was
--         'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR'
--
--     -   'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceImageFormatInfo2'::@tiling@
--         was
--         'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT'
--
--     -   the
--         'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceImageFormatInfo2'::@pNext@
--         chain included a
--         'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceExternalImageFormatInfo'
--         structure with a handle type included in the @handleTypes@
--         member for which mipmap image support is not required
--
--     -   image @format@ is one of those listed in
--         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion>
--
--     -   @flags@ contains
--         'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT'
--
-- -   @maxArrayLayers@ is the maximum number of array layers.
--     @maxArrayLayers@ /must/ be no less than
--     'PhysicalDeviceLimits'::@maxImageArrayLayers@, except when one of
--     the following conditions is true, in which case it /may/ instead be
--     @1@:
--
--     -   @tiling@ is
--         'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR'
--
--     -   @tiling@ is
--         'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL' and
--         @type@ is 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D'
--
--     -   @format@ is one of those listed in
--         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion>
--
-- -   If @tiling@ is
--     'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT',
--     then @maxArrayLayers@ /must/ not be 0.
--
-- -   @sampleCounts@ is a bitmask of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits'
--     specifying all the supported sample counts for this image as
--     described
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-supported-sample-counts below>.
--
-- -   @maxResourceSize@ is an upper bound on the total image size in
--     bytes, inclusive of all image subresources. Implementations /may/
--     have an address space limit on total size of a resource, which is
--     advertised by this property. @maxResourceSize@ /must/ be at least
--     231.
--
-- = Description
--
-- Note
--
-- There is no mechanism to query the size of an image before creating it,
-- to compare that size against @maxResourceSize@. If an application
-- attempts to create an image that exceeds this limit, the creation will
-- fail and 'Vulkan.Core10.Image.createImage' will return
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'. While the
-- advertised limit /must/ be at least 231, it /may/ not be possible to
-- create an image that approaches that size, particularly for
-- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D'.
--
-- If the combination of parameters to
-- 'getPhysicalDeviceImageFormatProperties' is not supported by the
-- implementation for use in 'Vulkan.Core10.Image.createImage', then all
-- members of 'ImageFormatProperties' will be filled with zero.
--
-- Note
--
-- Filling 'ImageFormatProperties' with zero for unsupported formats is an
-- exception to the usual rule that output structures have undefined
-- contents on error. This exception was unintentional, but is preserved
-- for backwards compatibility.
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.FundamentalTypes.Extent3D',
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalImageFormatPropertiesNV',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.ImageFormatProperties2',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlags',
-- 'getPhysicalDeviceImageFormatProperties'
data ImageFormatProperties = ImageFormatProperties
  { -- No documentation found for Nested "VkImageFormatProperties" "maxExtent"
    ImageFormatProperties -> Extent3D
maxExtent :: Extent3D
  , -- No documentation found for Nested "VkImageFormatProperties" "maxMipLevels"
    ImageFormatProperties -> Word32
maxMipLevels :: Word32
  , -- No documentation found for Nested "VkImageFormatProperties" "maxArrayLayers"
    ImageFormatProperties -> Word32
maxArrayLayers :: Word32
  , -- No documentation found for Nested "VkImageFormatProperties" "sampleCounts"
    ImageFormatProperties -> SampleCountFlags
sampleCounts :: SampleCountFlags
  , -- No documentation found for Nested "VkImageFormatProperties" "maxResourceSize"
    ImageFormatProperties -> DeviceSize
maxResourceSize :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageFormatProperties)
#endif
deriving instance Show ImageFormatProperties

instance ToCStruct ImageFormatProperties where
  withCStruct :: ImageFormatProperties
-> (("pImageFormatProperties" ::: Ptr ImageFormatProperties)
    -> IO b)
-> IO b
withCStruct x :: ImageFormatProperties
x f :: ("pImageFormatProperties" ::: Ptr ImageFormatProperties) -> IO b
f = Int
-> Int
-> (("pImageFormatProperties" ::: Ptr ImageFormatProperties)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pImageFormatProperties" ::: Ptr ImageFormatProperties) -> IO b)
 -> IO b)
-> (("pImageFormatProperties" ::: Ptr ImageFormatProperties)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pImageFormatProperties" ::: Ptr ImageFormatProperties
p -> ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> ImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pImageFormatProperties" ::: Ptr ImageFormatProperties
p ImageFormatProperties
x (("pImageFormatProperties" ::: Ptr ImageFormatProperties) -> IO b
f "pImageFormatProperties" ::: Ptr ImageFormatProperties
p)
  pokeCStruct :: ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> ImageFormatProperties -> IO b -> IO b
pokeCStruct p :: "pImageFormatProperties" ::: Ptr ImageFormatProperties
p ImageFormatProperties{..} 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 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Extent3D)) (Extent3D
maxExtent) (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 () -> 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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
maxMipLevels)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
maxArrayLayers)
    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 SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlags)) (SampleCountFlags
sampleCounts)
    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 DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
maxResourceSize)
    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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO b -> IO b
pokeZeroCStruct p :: "pImageFormatProperties" ::: Ptr ImageFormatProperties
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 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 Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Extent3D)) (Extent3D
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 () -> 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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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
$ ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    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 DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    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 ImageFormatProperties where
  peekCStruct :: ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> IO ImageFormatProperties
peekCStruct p :: "pImageFormatProperties" ::: Ptr ImageFormatProperties
p = do
    Extent3D
maxExtent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Extent3D))
    Word32
maxMipLevels <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    Word32
maxArrayLayers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    SampleCountFlags
sampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlags))
    DeviceSize
maxResourceSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pImageFormatProperties" ::: Ptr ImageFormatProperties
p ("pImageFormatProperties" ::: Ptr ImageFormatProperties)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
    ImageFormatProperties -> IO ImageFormatProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageFormatProperties -> IO ImageFormatProperties)
-> ImageFormatProperties -> IO ImageFormatProperties
forall a b. (a -> b) -> a -> b
$ Extent3D
-> Word32
-> Word32
-> SampleCountFlags
-> DeviceSize
-> ImageFormatProperties
ImageFormatProperties
             Extent3D
maxExtent Word32
maxMipLevels Word32
maxArrayLayers SampleCountFlags
sampleCounts DeviceSize
maxResourceSize

instance Zero ImageFormatProperties where
  zero :: ImageFormatProperties
zero = Extent3D
-> Word32
-> Word32
-> SampleCountFlags
-> DeviceSize
-> ImageFormatProperties
ImageFormatProperties
           Extent3D
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


-- | VkPhysicalDeviceFeatures - Structure describing the fine-grained
-- features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceFeatures' structure describe the
-- following features:
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Device.DeviceCreateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- 'getPhysicalDeviceFeatures'
data PhysicalDeviceFeatures = PhysicalDeviceFeatures
  { -- | @robustBufferAccess@ specifies that accesses to buffers are
    -- bounds-checked against the range of the buffer descriptor (as determined
    -- by 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo'::@range@,
    -- 'Vulkan.Core10.BufferView.BufferViewCreateInfo'::@range@, or the size of
    -- the buffer). Out of bounds accesses /must/ not cause application
    -- termination, and the effects of shader loads, stores, and atomics /must/
    -- conform to an implementation-dependent behavior as described below.
    --
    -- -   A buffer access is considered to be out of bounds if any of the
    --     following are true:
    --
    --     -   The pointer was formed by @OpImageTexelPointer@ and the
    --         coordinate is less than zero or greater than or equal to the
    --         number of whole elements in the bound range.
    --
    --     -   The pointer was not formed by @OpImageTexelPointer@ and the
    --         object pointed to is not wholly contained within the bound
    --         range. This includes accesses performed via /variable pointers/
    --         where the buffer descriptor being accessed cannot be statically
    --         determined. Uninitialized pointers and pointers equal to
    --         @OpConstantNull@ are treated as pointing to a zero-sized object,
    --         so all accesses through such pointers are considered to be out
    --         of bounds. Buffer accesses through buffer device addresses are
    --         not bounds-checked. If the
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-cooperativeMatrixRobustBufferAccess cooperativeMatrixRobustBufferAccess>
    --         feature is not enabled, then accesses using
    --         @OpCooperativeMatrixLoadNV@ and @OpCooperativeMatrixStoreNV@
    --         /may/ not be bounds-checked.
    --
    --         Note
    --
    --         If a SPIR-V @OpLoad@ instruction loads a structure and the tail
    --         end of the structure is out of bounds, then all members of the
    --         structure are considered out of bounds even if the members at
    --         the end are not statically used.
    --
    --     -   If
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is not enabled and any buffer access is determined to be out of
    --         bounds, then any other access of the same type (load, store, or
    --         atomic) to the same buffer that accesses an address less than 16
    --         bytes away from the out of bounds address /may/ also be
    --         considered out of bounds.
    --
    --     -   If the access is a load that reads from the same memory
    --         locations as a prior store in the same shader invocation, with
    --         no other intervening accesses to the same memory locations in
    --         that shader invocation, then the result of the load /may/ be the
    --         value stored by the store instruction, even if the access is out
    --         of bounds. If the load is @Volatile@, then an out of bounds load
    --         /must/ return the appropriate out of bounds value.
    --
    -- -   Accesses to descriptors written with a
    --     'Vulkan.Core10.APIConstants.NULL_HANDLE' resource or view are not
    --     considered to be out of bounds. Instead, each type of descriptor
    --     access defines a specific behavior for accesses to a null
    --     descriptor.
    --
    -- -   Out-of-bounds buffer loads will return any of the following values:
    --
    --     -   If the access is to a uniform buffer and
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, loads of offsets between the end of the descriptor
    --         range and the end of the descriptor range rounded up to a
    --         multiple of
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-robustUniformBufferAccessSizeAlignment robustUniformBufferAccessSizeAlignment>
    --         bytes /must/ return either zero values or the contents of the
    --         memory at the offset being loaded. Loads of offsets past the
    --         descriptor range rounded up to a multiple of
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-robustUniformBufferAccessSizeAlignment robustUniformBufferAccessSizeAlignment>
    --         bytes /must/ return zero values.
    --
    --     -   If the access is to a storage buffer and
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, loads of offsets between the end of the descriptor
    --         range and the end of the descriptor range rounded up to a
    --         multiple of
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-robustStorageBufferAccessSizeAlignment robustStorageBufferAccessSizeAlignment>
    --         bytes /must/ return either zero values or the contents of the
    --         memory at the offset being loaded. Loads of offsets past the
    --         descriptor range rounded up to a multiple of
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-robustStorageBufferAccessSizeAlignment robustStorageBufferAccessSizeAlignment>
    --         bytes /must/ return zero values. Similarly, stores to addresses
    --         between the end of the descriptor range and the end of the
    --         descriptor range rounded up to a multiple of
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-robustStorageBufferAccessSizeAlignment robustStorageBufferAccessSizeAlignment>
    --         bytes /may/ be discarded.
    --
    --     -   Non-atomic accesses to storage buffers that are a multiple of 32
    --         bits /may/ be decomposed into 32-bit accesses that are
    --         individually bounds-checked.
    --
    --     -   If the access is to an index buffer and
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, zero values /must/ be returned.
    --
    --     -   If the access is to a uniform texel buffer or storage texel
    --         buffer and
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, zero values /must/ be returned, and then
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-conversion-to-rgba Conversion to RGBA>
    --         is applied based on the buffer view’s format.
    --
    --     -   Values from anywhere within the memory range(s) bound to the
    --         buffer (possibly including bytes of memory past the end of the
    --         buffer, up to the end of the bound range).
    --
    --     -   Zero values, or (0,0,0,x) vectors for vector reads where x is a
    --         valid value represented in the type of the vector components and
    --         /may/ be any of:
    --
    --         -   0, 1, or the maximum representable positive integer value,
    --             for signed or unsigned integer components
    --
    --         -   0.0 or 1.0, for floating-point components
    --
    -- -   Out-of-bounds writes /may/ modify values within the memory range(s)
    --     bound to the buffer, but /must/ not modify any other memory.
    --
    --     -   If
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, out of bounds writes /must/ not modify any memory.
    --
    -- -   Out-of-bounds atomics /may/ modify values within the memory range(s)
    --     bound to the buffer, but /must/ not modify any other memory, and
    --     return an undefined value.
    --
    --     -   If
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --         is enabled, out of bounds atomics /must/ not modify any memory,
    --         and return an undefined value.
    --
    -- -   If
    --     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --     is disabled, vertex input attributes are considered out of bounds if
    --     the offset of the attribute in the bound vertex buffer range plus
    --     the size of the attribute is greater than either:
    --
    --     -   @vertexBufferRangeSize@, if @bindingStride@ == 0; or
    --
    --     -   (@vertexBufferRangeSize@ - (@vertexBufferRangeSize@ %
    --         @bindingStride@))
    --
    --     where @vertexBufferRangeSize@ is the byte size of the memory range
    --     bound to the vertex buffer binding and @bindingStride@ is the byte
    --     stride of the corresponding vertex input binding. Further, if any
    --     vertex input attribute using a specific vertex input binding is out
    --     of bounds, then all vertex input attributes using that vertex input
    --     binding for that vertex shader invocation are considered out of
    --     bounds.
    --
    --     -   If a vertex input attribute is out of bounds, it will be
    --         assigned one of the following values:
    --
    --         -   Values from anywhere within the memory range(s) bound to the
    --             buffer, converted according to the format of the attribute.
    --
    --         -   Zero values, format converted according to the format of the
    --             attribute.
    --
    --         -   Zero values, or (0,0,0,x) vectors, as described above.
    --
    -- -   If
    --     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    --     is enabled, vertex input attributes are considered out of bounds if
    --     the offset of the attribute in the bound vertex buffer range plus
    --     the size of the attribute is greater than the byte size of the
    --     memory range bound to the vertex buffer binding.
    --
    --     -   If a vertex input attribute is out of bounds, the
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input-extraction raw data>
    --         extracted are zero values, and missing G, B, or A components are
    --         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input-extraction filled with (0,0,1)>.
    --
    -- -   If @robustBufferAccess@ is not enabled, applications /must/ not
    --     perform out of bounds accesses.
    PhysicalDeviceFeatures -> Bool
robustBufferAccess :: Bool
  , -- | @fullDrawIndexUint32@ specifies the full 32-bit range of indices is
    -- supported for indexed draw calls when using a
    -- 'Vulkan.Core10.Enums.IndexType.IndexType' of
    -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT32'.
    -- @maxDrawIndexedIndexValue@ is the maximum index value that /may/ be used
    -- (aside from the primitive restart index, which is always 232-1 when the
    -- 'Vulkan.Core10.Enums.IndexType.IndexType' is
    -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT32'). If this feature is
    -- supported, @maxDrawIndexedIndexValue@ /must/ be 232-1; otherwise it
    -- /must/ be no smaller than 224-1. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxDrawIndexedIndexValue maxDrawIndexedIndexValue>.
    PhysicalDeviceFeatures -> Bool
fullDrawIndexUint32 :: Bool
  , -- | @imageCubeArray@ specifies whether image views with a
    -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of
    -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' /can/ be
    -- created, and that the corresponding @SampledCubeArray@ and
    -- @ImageCubeArray@ SPIR-V capabilities /can/ be used in shader code.
    PhysicalDeviceFeatures -> Bool
imageCubeArray :: Bool
  , -- | @independentBlend@ specifies whether the
    -- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState' settings are
    -- controlled independently per-attachment. If this feature is not enabled,
    -- the 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState' settings
    -- for all color attachments /must/ be identical. Otherwise, a different
    -- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState' /can/ be
    -- provided for each bound color attachment.
    PhysicalDeviceFeatures -> Bool
independentBlend :: Bool
  , -- | @geometryShader@ specifies whether geometry shaders are supported. If
    -- this feature is not enabled, the
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT' and
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
    -- enum values /must/ not be used. This also specifies whether shader
    -- modules /can/ declare the @Geometry@ capability.
    PhysicalDeviceFeatures -> Bool
geometryShader :: Bool
  , -- | @tessellationShader@ specifies whether tessellation control and
    -- evaluation shaders are supported. If this feature is not enabled, the
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT',
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT',
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT',
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT',
    -- and
    -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO'
    -- enum values /must/ not be used. This also specifies whether shader
    -- modules /can/ declare the @Tessellation@ capability.
    PhysicalDeviceFeatures -> Bool
tessellationShader :: Bool
  , -- | @sampleRateShading@ specifies whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-sampleshading Sample Shading>
    -- and multisample interpolation are supported. If this feature is not
    -- enabled, the @sampleShadingEnable@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' structure
    -- /must/ be set to 'Vulkan.Core10.FundamentalTypes.FALSE' and the
    -- @minSampleShading@ member is ignored. This also specifies whether shader
    -- modules /can/ declare the @SampleRateShading@ capability.
    PhysicalDeviceFeatures -> Bool
sampleRateShading :: Bool
  , -- | @dualSrcBlend@ specifies whether blend operations which take two sources
    -- are supported. If this feature is not enabled, the
    -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_COLOR',
    -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_COLOR',
    -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_ALPHA', and
    -- 'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA' enum
    -- values /must/ not be used as source or destination blending factors. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb>.
    PhysicalDeviceFeatures -> Bool
dualSrcBlend :: Bool
  , -- | @logicOp@ specifies whether logic operations are supported. If this
    -- feature is not enabled, the @logicOpEnable@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo' structure
    -- /must/ be set to 'Vulkan.Core10.FundamentalTypes.FALSE', and the
    -- @logicOp@ member is ignored.
    PhysicalDeviceFeatures -> Bool
logicOp :: Bool
  , -- | @multiDrawIndirect@ specifies whether multiple draw indirect is
    -- supported. If this feature is not enabled, the @drawCount@ parameter to
    -- the 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndirect' and
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect' commands
    -- /must/ be 0 or 1. The @maxDrawIndirectCount@ member of the
    -- 'PhysicalDeviceLimits' structure /must/ also be 1 if this feature is not
    -- supported. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxDrawIndirectCount maxDrawIndirectCount>.
    PhysicalDeviceFeatures -> Bool
multiDrawIndirect :: Bool
  , -- | @drawIndirectFirstInstance@ specifies whether indirect draw calls
    -- support the @firstInstance@ parameter. If this feature is not enabled,
    -- the @firstInstance@ member of all
    -- 'Vulkan.Core10.OtherTypes.DrawIndirectCommand' and
    -- 'Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand' structures that
    -- are provided to the
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndirect' and
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect' commands
    -- /must/ be 0.
    PhysicalDeviceFeatures -> Bool
drawIndirectFirstInstance :: Bool
  , -- | @depthClamp@ specifies whether depth clamping is supported. If this
    -- feature is not enabled, the @depthClampEnable@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' structure
    -- /must/ be set to 'Vulkan.Core10.FundamentalTypes.FALSE'. Otherwise,
    -- setting @depthClampEnable@ to 'Vulkan.Core10.FundamentalTypes.TRUE' will
    -- enable depth clamping.
    PhysicalDeviceFeatures -> Bool
depthClamp :: Bool
  , -- | @depthBiasClamp@ specifies whether depth bias clamping is supported. If
    -- this feature is not enabled, the @depthBiasClamp@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' structure
    -- /must/ be set to 0.0 unless the
    -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS' dynamic
    -- state is enabled, and the @depthBiasClamp@ parameter to
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdSetDepthBias' /must/ be set to
    -- 0.0.
    PhysicalDeviceFeatures -> Bool
depthBiasClamp :: Bool
  , -- | @fillModeNonSolid@ specifies whether point and wireframe fill modes are
    -- supported. If this feature is not enabled, the
    -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_POINT' and
    -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_LINE' enum values /must/
    -- not be used.
    PhysicalDeviceFeatures -> Bool
fillModeNonSolid :: Bool
  , -- | @depthBounds@ specifies whether depth bounds tests are supported. If
    -- this feature is not enabled, the @depthBoundsTestEnable@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' structure
    -- /must/ be set to 'Vulkan.Core10.FundamentalTypes.FALSE'. When
    -- @depthBoundsTestEnable@ is set to
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', the @minDepthBounds@ and
    -- @maxDepthBounds@ members of the
    -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' structure
    -- are ignored.
    PhysicalDeviceFeatures -> Bool
depthBounds :: Bool
  , -- | @wideLines@ specifies whether lines with width other than 1.0 are
    -- supported. If this feature is not enabled, the @lineWidth@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' structure
    -- /must/ be set to 1.0 unless the
    -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH' dynamic
    -- state is enabled, and the @lineWidth@ parameter to
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdSetLineWidth' /must/ be set to
    -- 1.0. When this feature is supported, the range and granularity of
    -- supported line widths are indicated by the @lineWidthRange@ and
    -- @lineWidthGranularity@ members of the 'PhysicalDeviceLimits' structure,
    -- respectively.
    PhysicalDeviceFeatures -> Bool
wideLines :: Bool
  , -- | @largePoints@ specifies whether points with size greater than 1.0 are
    -- supported. If this feature is not enabled, only a point size of 1.0
    -- written by a shader is supported. The range and granularity of supported
    -- point sizes are indicated by the @pointSizeRange@ and
    -- @pointSizeGranularity@ members of the 'PhysicalDeviceLimits' structure,
    -- respectively.
    PhysicalDeviceFeatures -> Bool
largePoints :: Bool
  , -- | @alphaToOne@ specifies whether the implementation is able to replace the
    -- alpha value of the color fragment output from the fragment shader with
    -- the maximum representable alpha value for fixed-point colors or 1.0 for
    -- floating-point colors. If this feature is not enabled, then the
    -- @alphaToOneEnable@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' structure
    -- /must/ be set to 'Vulkan.Core10.FundamentalTypes.FALSE'. Otherwise
    -- setting @alphaToOneEnable@ to 'Vulkan.Core10.FundamentalTypes.TRUE' will
    -- enable alpha-to-one behavior.
    PhysicalDeviceFeatures -> Bool
alphaToOne :: Bool
  , -- | @multiViewport@ specifies whether more than one viewport is supported.
    -- If this feature is not enabled:
    --
    -- -   The @viewportCount@ and @scissorCount@ members of the
    --     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' structure
    --     /must/ be set to 1.
    --
    -- -   The @firstViewport@ and @viewportCount@ parameters to the
    --     'Vulkan.Core10.CommandBufferBuilding.cmdSetViewport' command /must/
    --     be set to 0 and 1, respectively.
    --
    -- -   The @firstScissor@ and @scissorCount@ parameters to the
    --     'Vulkan.Core10.CommandBufferBuilding.cmdSetScissor' command /must/
    --     be set to 0 and 1, respectively.
    --
    -- -   The @exclusiveScissorCount@ member of the
    --     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
    --     structure /must/ be set to 0 or 1.
    --
    -- -   The @firstExclusiveScissor@ and @exclusiveScissorCount@ parameters
    --     to the
    --     'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV'
    --     command /must/ be set to 0 and 1, respectively.
    PhysicalDeviceFeatures -> Bool
multiViewport :: Bool
  , -- | @samplerAnisotropy@ specifies whether anisotropic filtering is
    -- supported. If this feature is not enabled, the @anisotropyEnable@ member
    -- of the 'Vulkan.Core10.Sampler.SamplerCreateInfo' structure /must/ be
    -- 'Vulkan.Core10.FundamentalTypes.FALSE'.
    PhysicalDeviceFeatures -> Bool
samplerAnisotropy :: Bool
  , -- | @textureCompressionETC2@ specifies whether all of the ETC2 and EAC
    -- compressed texture formats are supported. If this feature is enabled,
    -- then the
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT',
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
    -- and
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
    -- features /must/ be supported in @optimalTilingFeatures@ for the
    -- following formats:
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_EAC_R11_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_EAC_R11_SNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_EAC_R11G11_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_EAC_R11G11_SNORM_BLOCK'
    --
    -- To query for additional properties, or if the feature is not enabled,
    -- 'getPhysicalDeviceFormatProperties' and
    -- 'getPhysicalDeviceImageFormatProperties' /can/ be used to check for
    -- supported properties of individual formats as normal.
    PhysicalDeviceFeatures -> Bool
textureCompressionETC2 :: Bool
  , -- | @textureCompressionASTC_LDR@ specifies whether all of the ASTC LDR
    -- compressed texture formats are supported. If this feature is enabled,
    -- then the
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT',
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
    -- and
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
    -- features /must/ be supported in @optimalTilingFeatures@ for the
    -- following formats:
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_4x4_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_4x4_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_5x4_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_5x4_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_5x5_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_5x5_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_6x5_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_6x5_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_6x6_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_6x6_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x5_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x5_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x6_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x6_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x8_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_8x8_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x5_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x5_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x6_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x6_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x8_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x8_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x10_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_10x10_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_12x10_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_12x10_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_12x12_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_ASTC_12x12_SRGB_BLOCK'
    --
    -- To query for additional properties, or if the feature is not enabled,
    -- 'getPhysicalDeviceFormatProperties' and
    -- 'getPhysicalDeviceImageFormatProperties' /can/ be used to check for
    -- supported properties of individual formats as normal.
    PhysicalDeviceFeatures -> Bool
textureCompressionASTC_LDR :: Bool
  , -- | @textureCompressionBC@ specifies whether all of the BC compressed
    -- texture formats are supported. If this feature is enabled, then the
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT',
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
    -- and
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
    -- features /must/ be supported in @optimalTilingFeatures@ for the
    -- following formats:
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC1_RGB_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC1_RGB_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC1_RGBA_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC1_RGBA_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC2_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC2_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC3_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC3_SRGB_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC4_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC4_SNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC5_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC5_SNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC6H_UFLOAT_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC6H_SFLOAT_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC7_UNORM_BLOCK'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_BC7_SRGB_BLOCK'
    --
    -- To query for additional properties, or if the feature is not enabled,
    -- 'getPhysicalDeviceFormatProperties' and
    -- 'getPhysicalDeviceImageFormatProperties' /can/ be used to check for
    -- supported properties of individual formats as normal.
    PhysicalDeviceFeatures -> Bool
textureCompressionBC :: Bool
  , -- | @occlusionQueryPrecise@ specifies whether occlusion queries returning
    -- actual sample counts are supported. Occlusion queries are created in a
    -- 'Vulkan.Core10.Handles.QueryPool' by specifying the @queryType@ of
    -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_OCCLUSION' in the
    -- 'Vulkan.Core10.Query.QueryPoolCreateInfo' structure which is passed to
    -- 'Vulkan.Core10.Query.createQueryPool'. If this feature is enabled,
    -- queries of this type /can/ enable
    -- 'Vulkan.Core10.Enums.QueryControlFlagBits.QUERY_CONTROL_PRECISE_BIT' in
    -- the @flags@ parameter to
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery'. If this feature is
    -- not supported, the implementation supports only boolean occlusion
    -- queries. When any samples are passed, boolean queries will return a
    -- non-zero result value, otherwise a result value of zero is returned.
    -- When this feature is enabled and
    -- 'Vulkan.Core10.Enums.QueryControlFlagBits.QUERY_CONTROL_PRECISE_BIT' is
    -- set, occlusion queries will report the actual number of samples passed.
    PhysicalDeviceFeatures -> Bool
occlusionQueryPrecise :: Bool
  , -- | @pipelineStatisticsQuery@ specifies whether the pipeline statistics
    -- queries are supported. If this feature is not enabled, queries of type
    -- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PIPELINE_STATISTICS' /cannot/
    -- be created, and none of the
    -- 'Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits.QueryPipelineStatisticFlagBits'
    -- bits /can/ be set in the @pipelineStatistics@ member of the
    -- 'Vulkan.Core10.Query.QueryPoolCreateInfo' structure.
    PhysicalDeviceFeatures -> Bool
pipelineStatisticsQuery :: Bool
  , -- | @vertexPipelineStoresAndAtomics@ specifies whether storage buffers and
    -- images support stores and atomic operations in the vertex, tessellation,
    -- and geometry shader stages. If this feature is not enabled, all storage
    -- image, storage texel buffers, and storage buffer variables used by these
    -- stages in shader modules /must/ be decorated with the @NonWritable@
    -- decoration (or the @readonly@ memory qualifier in GLSL).
    PhysicalDeviceFeatures -> Bool
vertexPipelineStoresAndAtomics :: Bool
  , -- | @fragmentStoresAndAtomics@ specifies whether storage buffers and images
    -- support stores and atomic operations in the fragment shader stage. If
    -- this feature is not enabled, all storage image, storage texel buffers,
    -- and storage buffer variables used by the fragment stage in shader
    -- modules /must/ be decorated with the @NonWritable@ decoration (or the
    -- @readonly@ memory qualifier in GLSL).
    PhysicalDeviceFeatures -> Bool
fragmentStoresAndAtomics :: Bool
  , -- | @shaderTessellationAndGeometryPointSize@ specifies whether the
    -- @PointSize@ built-in decoration is available in the tessellation
    -- control, tessellation evaluation, and geometry shader stages. If this
    -- feature is not enabled, members decorated with the @PointSize@ built-in
    -- decoration /must/ not be read from or written to and all points written
    -- from a tessellation or geometry shader will have a size of 1.0. This
    -- also specifies whether shader modules /can/ declare the
    -- @TessellationPointSize@ capability for tessellation control and
    -- evaluation shaders, or if the shader modules /can/ declare the
    -- @GeometryPointSize@ capability for geometry shaders. An implementation
    -- supporting this feature /must/ also support one or both of the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader>
    -- or
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader>
    -- features.
    PhysicalDeviceFeatures -> Bool
shaderTessellationAndGeometryPointSize :: Bool
  , -- | @shaderImageGatherExtended@ specifies whether the extended set of image
    -- gather instructions are available in shader code. If this feature is not
    -- enabled, the @OpImage@*@Gather@ instructions do not support the @Offset@
    -- and @ConstOffsets@ operands. This also specifies whether shader modules
    -- /can/ declare the @ImageGatherExtended@ capability.
    PhysicalDeviceFeatures -> Bool
shaderImageGatherExtended :: Bool
  , -- | @shaderStorageImageExtendedFormats@ specifies whether all the “storage
    -- image extended formats” below are supported; if this feature is
    -- supported, then the
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_BIT'
    -- /must/ be supported in @optimalTilingFeatures@ for the following
    -- formats:
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16_SFLOAT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_B10G11R11_UFLOAT_PACK32'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16_SFLOAT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16B16A16_UNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_A2B10G10R10_UNORM_PACK32'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16_UNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8G8_UNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16_UNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8_UNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16B16A16_SNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16_SNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8G8_SNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16_SNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8_SNORM'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16_SINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8G8_SINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16_SINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8_SINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_A2B10G10R10_UINT_PACK32'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16G16_UINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8G8_UINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R16_UINT'
    --
    -- -   'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT'
    --
    -- Note
    --
    -- @shaderStorageImageExtendedFormats@ feature only adds a guarantee of
    -- format support, which is specified for the whole physical device.
    -- Therefore enabling or disabling the feature via
    -- 'Vulkan.Core10.Device.createDevice' has no practical effect.
    --
    -- To query for additional properties, or if the feature is not supported,
    -- 'getPhysicalDeviceFormatProperties' and
    -- 'getPhysicalDeviceImageFormatProperties' /can/ be used to check for
    -- supported properties of individual formats, as usual rules allow.
    --
    -- 'Vulkan.Core10.Enums.Format.FORMAT_R32G32_UINT',
    -- 'Vulkan.Core10.Enums.Format.FORMAT_R32G32_SINT', and
    -- 'Vulkan.Core10.Enums.Format.FORMAT_R32G32_SFLOAT' from
    -- @StorageImageExtendedFormats@ SPIR-V capability, are already covered by
    -- core Vulkan
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-mandatory-features-32bit mandatory format support>.
    PhysicalDeviceFeatures -> Bool
shaderStorageImageExtendedFormats :: Bool
  , -- | @shaderStorageImageMultisample@ specifies whether multisampled storage
    -- images are supported. If this feature is not enabled, images that are
    -- created with a @usage@ that includes
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_STORAGE_BIT' /must/
    -- be created with @samples@ equal to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'. This also
    -- specifies whether shader modules /can/ declare the
    -- @StorageImageMultisample@ and @ImageMSArray@ capabilities.
    PhysicalDeviceFeatures -> Bool
shaderStorageImageMultisample :: Bool
  , -- | @shaderStorageImageReadWithoutFormat@ specifies whether storage images
    -- require a format qualifier to be specified when reading from storage
    -- images. If this feature is not enabled, the @OpImageRead@ instruction
    -- /must/ not have an @OpTypeImage@ of @Unknown@. This also specifies
    -- whether shader modules /can/ declare the @StorageImageReadWithoutFormat@
    -- capability.
    PhysicalDeviceFeatures -> Bool
shaderStorageImageReadWithoutFormat :: Bool
  , -- | @shaderStorageImageWriteWithoutFormat@ specifies whether storage images
    -- require a format qualifier to be specified when writing to storage
    -- images. If this feature is not enabled, the @OpImageWrite@ instruction
    -- /must/ not have an @OpTypeImage@ of @Unknown@. This also specifies
    -- whether shader modules /can/ declare the
    -- @StorageImageWriteWithoutFormat@ capability.
    PhysicalDeviceFeatures -> Bool
shaderStorageImageWriteWithoutFormat :: Bool
  , -- | @shaderUniformBufferArrayDynamicIndexing@ specifies whether arrays of
    -- uniform buffers /can/ be indexed by /dynamically uniform/ integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also specifies whether shader modules
    -- /can/ declare the @UniformBufferArrayDynamicIndexing@ capability.
    PhysicalDeviceFeatures -> Bool
shaderUniformBufferArrayDynamicIndexing :: Bool
  , -- | @shaderSampledImageArrayDynamicIndexing@ specifies whether arrays of
    -- samplers or sampled images /can/ be indexed by dynamically uniform
    -- integer expressions in shader code. If this feature is not enabled,
    -- resources with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- or 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also specifies whether shader modules
    -- /can/ declare the @SampledImageArrayDynamicIndexing@ capability.
    PhysicalDeviceFeatures -> Bool
shaderSampledImageArrayDynamicIndexing :: Bool
  , -- | @shaderStorageBufferArrayDynamicIndexing@ specifies whether arrays of
    -- storage buffers /can/ be indexed by dynamically uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also specifies whether shader modules
    -- /can/ declare the @StorageBufferArrayDynamicIndexing@ capability.
    PhysicalDeviceFeatures -> Bool
shaderStorageBufferArrayDynamicIndexing :: Bool
  , -- | @shaderStorageImageArrayDynamicIndexing@ specifies whether arrays of
    -- storage images /can/ be indexed by dynamically uniform integer
    -- expressions in shader code. If this feature is not enabled, resources
    -- with a descriptor type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'
    -- /must/ be indexed only by constant integral expressions when aggregated
    -- into arrays in shader code. This also specifies whether shader modules
    -- /can/ declare the @StorageImageArrayDynamicIndexing@ capability.
    PhysicalDeviceFeatures -> Bool
shaderStorageImageArrayDynamicIndexing :: Bool
  , -- | @shaderClipDistance@ specifies whether clip distances are supported in
    -- shader code. If this feature is not enabled, any members decorated with
    -- the @ClipDistance@ built-in decoration /must/ not be read from or
    -- written to in shader modules. This also specifies whether shader modules
    -- /can/ declare the @ClipDistance@ capability.
    PhysicalDeviceFeatures -> Bool
shaderClipDistance :: Bool
  , -- | @shaderCullDistance@ specifies whether cull distances are supported in
    -- shader code. If this feature is not enabled, any members decorated with
    -- the @CullDistance@ built-in decoration /must/ not be read from or
    -- written to in shader modules. This also specifies whether shader modules
    -- /can/ declare the @CullDistance@ capability.
    PhysicalDeviceFeatures -> Bool
shaderCullDistance :: Bool
  , -- | @shaderFloat64@ specifies whether 64-bit floats (doubles) are supported
    -- in shader code. If this feature is not enabled, 64-bit floating-point
    -- types /must/ not be used in shader code. This also specifies whether
    -- shader modules /can/ declare the @Float64@ capability. Declaring and
    -- using 64-bit floats is enabled for all storage classes that SPIR-V
    -- allows with the @Float64@ capability.
    PhysicalDeviceFeatures -> Bool
shaderFloat64 :: Bool
  , -- | @shaderInt64@ specifies whether 64-bit integers (signed and unsigned)
    -- are supported in shader code. If this feature is not enabled, 64-bit
    -- integer types /must/ not be used in shader code. This also specifies
    -- whether shader modules /can/ declare the @Int64@ capability. Declaring
    -- and using 64-bit integers is enabled for all storage classes that SPIR-V
    -- allows with the @Int64@ capability.
    PhysicalDeviceFeatures -> Bool
shaderInt64 :: Bool
  , -- | @shaderInt16@ specifies whether 16-bit integers (signed and unsigned)
    -- are supported in shader code. If this feature is not enabled, 16-bit
    -- integer types /must/ not be used in shader code. This also specifies
    -- whether shader modules /can/ declare the @Int16@ capability. However,
    -- this only enables a subset of the storage classes that SPIR-V allows for
    -- the @Int16@ SPIR-V capability: Declaring and using 16-bit integers in
    -- the @Private@, @Workgroup@, and @Function@ storage classes is enabled,
    -- while declaring them in the interface storage classes (e.g.,
    -- @UniformConstant@, @Uniform@, @StorageBuffer@, @Input@, @Output@, and
    -- @PushConstant@) is not enabled.
    PhysicalDeviceFeatures -> Bool
shaderInt16 :: Bool
  , -- | @shaderResourceResidency@ specifies whether image operations that return
    -- resource residency information are supported in shader code. If this
    -- feature is not enabled, the @OpImageSparse@* instructions /must/ not be
    -- used in shader code. This also specifies whether shader modules /can/
    -- declare the @SparseResidency@ capability. The feature requires at least
    -- one of the @sparseResidency*@ features to be supported.
    PhysicalDeviceFeatures -> Bool
shaderResourceResidency :: Bool
  , -- | @shaderResourceMinLod@ specifies whether image operations specifying the
    -- minimum resource LOD are supported in shader code. If this feature is
    -- not enabled, the @MinLod@ image operand /must/ not be used in shader
    -- code. This also specifies whether shader modules /can/ declare the
    -- @MinLod@ capability.
    PhysicalDeviceFeatures -> Bool
shaderResourceMinLod :: Bool
  , -- | @sparseBinding@ specifies whether resource memory /can/ be managed at
    -- opaque sparse block level instead of at the object level. If this
    -- feature is not enabled, resource memory /must/ be bound only on a
    -- per-object basis using the
    -- 'Vulkan.Core10.MemoryManagement.bindBufferMemory' and
    -- 'Vulkan.Core10.MemoryManagement.bindImageMemory' commands. In this case,
    -- buffers and images /must/ not be created with
    -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_BINDING_BIT'
    -- and
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_BINDING_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Buffer.BufferCreateInfo'
    -- and 'Vulkan.Core10.Image.ImageCreateInfo' structures, respectively.
    -- Otherwise resource memory /can/ be managed as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory-sparseresourcefeatures Sparse Resource Features>.
    PhysicalDeviceFeatures -> Bool
sparseBinding :: Bool
  , -- | @sparseResidencyBuffer@ specifies whether the device /can/ access
    -- partially resident buffers. If this feature is not enabled, buffers
    -- /must/ not be created with
    -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Buffer.BufferCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidencyBuffer :: Bool
  , -- | @sparseResidencyImage2D@ specifies whether the device /can/ access
    -- partially resident 2D images with 1 sample per pixel. If this feature is
    -- not enabled, images with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and @samples@ set to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' /must/ not
    -- be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidencyImage2D :: Bool
  , -- | @sparseResidencyImage3D@ specifies whether the device /can/ access
    -- partially resident 3D images. If this feature is not enabled, images
    -- with an @imageType@ of 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D'
    -- /must/ not be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidencyImage3D :: Bool
  , -- | @sparseResidency2Samples@ specifies whether the physical device /can/
    -- access partially resident 2D images with 2 samples per pixel. If this
    -- feature is not enabled, images with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and @samples@ set to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_2_BIT' /must/ not
    -- be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidency2Samples :: Bool
  , -- | @sparseResidency4Samples@ specifies whether the physical device /can/
    -- access partially resident 2D images with 4 samples per pixel. If this
    -- feature is not enabled, images with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and @samples@ set to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_4_BIT' /must/ not
    -- be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidency4Samples :: Bool
  , -- | @sparseResidency8Samples@ specifies whether the physical device /can/
    -- access partially resident 2D images with 8 samples per pixel. If this
    -- feature is not enabled, images with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and @samples@ set to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_8_BIT' /must/ not
    -- be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidency8Samples :: Bool
  , -- | @sparseResidency16Samples@ specifies whether the physical device /can/
    -- access partially resident 2D images with 16 samples per pixel. If this
    -- feature is not enabled, images with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and @samples@ set to
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_16_BIT' /must/ not
    -- be created with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
    -- set in the @flags@ member of the 'Vulkan.Core10.Image.ImageCreateInfo'
    -- structure.
    PhysicalDeviceFeatures -> Bool
sparseResidency16Samples :: Bool
  , -- | @sparseResidencyAliased@ specifies whether the physical device /can/
    -- correctly access data aliased into multiple locations. If this feature
    -- is not enabled, the
    -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_ALIASED_BIT'
    -- and
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_ALIASED_BIT'
    -- enum values /must/ not be used in @flags@ members of the
    -- 'Vulkan.Core10.Buffer.BufferCreateInfo' and
    -- 'Vulkan.Core10.Image.ImageCreateInfo' structures, respectively.
    PhysicalDeviceFeatures -> Bool
sparseResidencyAliased :: Bool
  , -- | @variableMultisampleRate@ specifies whether all pipelines that will be
    -- bound to a command buffer during a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments subpass which uses no attachments>
    -- /must/ have the same value for
    -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@.
    -- If set to 'Vulkan.Core10.FundamentalTypes.TRUE', the implementation
    -- supports variable multisample rates in a subpass which uses no
    -- attachments. If set to 'Vulkan.Core10.FundamentalTypes.FALSE', then all
    -- pipelines bound in such a subpass /must/ have the same multisample rate.
    -- This has no effect in situations where a subpass uses any attachments.
    PhysicalDeviceFeatures -> Bool
variableMultisampleRate :: Bool
  , -- | @inheritedQueries@ specifies whether a secondary command buffer /may/ be
    -- executed while a query is active.
    PhysicalDeviceFeatures -> Bool
inheritedQueries :: Bool
  }
  deriving (Typeable, PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool
(PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool)
-> (PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool)
-> Eq PhysicalDeviceFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool
$c/= :: PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool
== :: PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool
$c== :: PhysicalDeviceFeatures -> PhysicalDeviceFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceFeatures)
#endif
deriving instance Show PhysicalDeviceFeatures

instance ToCStruct PhysicalDeviceFeatures where
  withCStruct :: PhysicalDeviceFeatures
-> (("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b) -> IO b
withCStruct x :: PhysicalDeviceFeatures
x f :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b
f = Int
-> Int
-> (("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 220 4 ((("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b) -> IO b)
-> (("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pFeatures" ::: Ptr PhysicalDeviceFeatures
p -> ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pFeatures" ::: Ptr PhysicalDeviceFeatures
p PhysicalDeviceFeatures
x (("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b
f "pFeatures" ::: Ptr PhysicalDeviceFeatures
p)
  pokeCStruct :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures -> IO b -> IO b
pokeCStruct p :: "pFeatures" ::: Ptr PhysicalDeviceFeatures
p PhysicalDeviceFeatures{..} f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
fullDrawIndexUint32))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imageCubeArray))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentBlend))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
geometryShader))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
tessellationShader))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sampleRateShading))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dualSrcBlend))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
logicOp))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiDrawIndirect))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
drawIndirectFirstInstance))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthClamp))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBiasClamp))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
fillModeNonSolid))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBounds))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
wideLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
largePoints))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
alphaToOne))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiViewport))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerAnisotropy))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
textureCompressionETC2))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
textureCompressionASTC_LDR))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
textureCompressionBC))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
occlusionQueryPrecise))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
pipelineStatisticsQuery))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vertexPipelineStoresAndAtomics))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
fragmentStoresAndAtomics))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderTessellationAndGeometryPointSize))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderImageGatherExtended))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageExtendedFormats))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageMultisample))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageReadWithoutFormat))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageWriteWithoutFormat))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderClipDistance))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderCullDistance))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderFloat64))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInt64))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInt16))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderResourceResidency))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderResourceMinLod))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseBinding))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidencyBuffer))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidencyImage2D))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidencyImage3D))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidency2Samples))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidency4Samples))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidency8Samples))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidency16Samples))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sparseResidencyAliased))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variableMultisampleRate))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
inheritedQueries))
    IO b
f
  cStructSize :: Int
cStructSize = 220
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> IO b -> IO b
pokeZeroCStruct p :: "pFeatures" ::: Ptr PhysicalDeviceFeatures
p f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceFeatures where
  peekCStruct :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> IO PhysicalDeviceFeatures
peekCStruct p :: "pFeatures" ::: Ptr PhysicalDeviceFeatures
p = do
    Bool32
robustBufferAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32))
    Bool32
fullDrawIndexUint32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32))
    Bool32
imageCubeArray <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32))
    Bool32
independentBlend <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32))
    Bool32
geometryShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
tessellationShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
sampleRateShading <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
dualSrcBlend <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
logicOp <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
multiDrawIndirect <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
drawIndirectFirstInstance <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
depthClamp <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Bool32
depthBiasClamp <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32))
    Bool32
fillModeNonSolid <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32))
    Bool32
depthBounds <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32))
    Bool32
wideLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32))
    Bool32
largePoints <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32))
    Bool32
alphaToOne <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32))
    Bool32
multiViewport <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32))
    Bool32
samplerAnisotropy <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32))
    Bool32
textureCompressionETC2 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32))
    Bool32
textureCompressionASTC_LDR <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32))
    Bool32
textureCompressionBC <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32))
    Bool32
occlusionQueryPrecise <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32))
    Bool32
pipelineStatisticsQuery <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32))
    Bool32
vertexPipelineStoresAndAtomics <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32))
    Bool32
fragmentStoresAndAtomics <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32))
    Bool32
shaderTessellationAndGeometryPointSize <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32))
    Bool32
shaderImageGatherExtended <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32))
    Bool32
shaderStorageImageExtendedFormats <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32))
    Bool32
shaderStorageImageMultisample <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32))
    Bool32
shaderStorageImageReadWithoutFormat <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32))
    Bool32
shaderStorageImageWriteWithoutFormat <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32))
    Bool32
shaderUniformBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32))
    Bool32
shaderClipDistance <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32))
    Bool32
shaderCullDistance <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32))
    Bool32
shaderFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32))
    Bool32
shaderInt64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32))
    Bool32
shaderInt16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32))
    Bool32
shaderResourceResidency <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32))
    Bool32
shaderResourceMinLod <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32))
    Bool32
sparseBinding <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32))
    Bool32
sparseResidencyBuffer <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32))
    Bool32
sparseResidencyImage2D <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32))
    Bool32
sparseResidencyImage3D <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32))
    Bool32
sparseResidency2Samples <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32))
    Bool32
sparseResidency4Samples <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32))
    Bool32
sparseResidency8Samples <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32))
    Bool32
sparseResidency16Samples <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Bool32))
    Bool32
sparseResidencyAliased <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Bool32))
    Bool32
variableMultisampleRate <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Bool32))
    Bool32
inheritedQueries <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pFeatures" ::: Ptr PhysicalDeviceFeatures
p ("pFeatures" ::: Ptr PhysicalDeviceFeatures) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Bool32))
    PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceFeatures
PhysicalDeviceFeatures
             (Bool32 -> Bool
bool32ToBool Bool32
robustBufferAccess) (Bool32 -> Bool
bool32ToBool Bool32
fullDrawIndexUint32) (Bool32 -> Bool
bool32ToBool Bool32
imageCubeArray) (Bool32 -> Bool
bool32ToBool Bool32
independentBlend) (Bool32 -> Bool
bool32ToBool Bool32
geometryShader) (Bool32 -> Bool
bool32ToBool Bool32
tessellationShader) (Bool32 -> Bool
bool32ToBool Bool32
sampleRateShading) (Bool32 -> Bool
bool32ToBool Bool32
dualSrcBlend) (Bool32 -> Bool
bool32ToBool Bool32
logicOp) (Bool32 -> Bool
bool32ToBool Bool32
multiDrawIndirect) (Bool32 -> Bool
bool32ToBool Bool32
drawIndirectFirstInstance) (Bool32 -> Bool
bool32ToBool Bool32
depthClamp) (Bool32 -> Bool
bool32ToBool Bool32
depthBiasClamp) (Bool32 -> Bool
bool32ToBool Bool32
fillModeNonSolid) (Bool32 -> Bool
bool32ToBool Bool32
depthBounds) (Bool32 -> Bool
bool32ToBool Bool32
wideLines) (Bool32 -> Bool
bool32ToBool Bool32
largePoints) (Bool32 -> Bool
bool32ToBool Bool32
alphaToOne) (Bool32 -> Bool
bool32ToBool Bool32
multiViewport) (Bool32 -> Bool
bool32ToBool Bool32
samplerAnisotropy) (Bool32 -> Bool
bool32ToBool Bool32
textureCompressionETC2) (Bool32 -> Bool
bool32ToBool Bool32
textureCompressionASTC_LDR) (Bool32 -> Bool
bool32ToBool Bool32
textureCompressionBC) (Bool32 -> Bool
bool32ToBool Bool32
occlusionQueryPrecise) (Bool32 -> Bool
bool32ToBool Bool32
pipelineStatisticsQuery) (Bool32 -> Bool
bool32ToBool Bool32
vertexPipelineStoresAndAtomics) (Bool32 -> Bool
bool32ToBool Bool32
fragmentStoresAndAtomics) (Bool32 -> Bool
bool32ToBool Bool32
shaderTessellationAndGeometryPointSize) (Bool32 -> Bool
bool32ToBool Bool32
shaderImageGatherExtended) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageExtendedFormats) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageMultisample) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageReadWithoutFormat) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageWriteWithoutFormat) (Bool32 -> Bool
bool32ToBool Bool32
shaderUniformBufferArrayDynamicIndexing) (Bool32 -> Bool
bool32ToBool Bool32
shaderSampledImageArrayDynamicIndexing) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageBufferArrayDynamicIndexing) (Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageArrayDynamicIndexing) (Bool32 -> Bool
bool32ToBool Bool32
shaderClipDistance) (Bool32 -> Bool
bool32ToBool Bool32
shaderCullDistance) (Bool32 -> Bool
bool32ToBool Bool32
shaderFloat64) (Bool32 -> Bool
bool32ToBool Bool32
shaderInt64) (Bool32 -> Bool
bool32ToBool Bool32
shaderInt16) (Bool32 -> Bool
bool32ToBool Bool32
shaderResourceResidency) (Bool32 -> Bool
bool32ToBool Bool32
shaderResourceMinLod) (Bool32 -> Bool
bool32ToBool Bool32
sparseBinding) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidencyBuffer) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidencyImage2D) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidencyImage3D) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidency2Samples) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidency4Samples) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidency8Samples) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidency16Samples) (Bool32 -> Bool
bool32ToBool Bool32
sparseResidencyAliased) (Bool32 -> Bool
bool32ToBool Bool32
variableMultisampleRate) (Bool32 -> Bool
bool32ToBool Bool32
inheritedQueries)

instance Storable PhysicalDeviceFeatures where
  sizeOf :: PhysicalDeviceFeatures -> Int
sizeOf ~PhysicalDeviceFeatures
_ = 220
  alignment :: PhysicalDeviceFeatures -> Int
alignment ~PhysicalDeviceFeatures
_ = 4
  peek :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> IO PhysicalDeviceFeatures
peek = ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> IO PhysicalDeviceFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures -> IO ()
poke ptr :: "pFeatures" ::: Ptr PhysicalDeviceFeatures
ptr poked :: PhysicalDeviceFeatures
poked = ("pFeatures" ::: Ptr PhysicalDeviceFeatures)
-> PhysicalDeviceFeatures -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pFeatures" ::: Ptr PhysicalDeviceFeatures
ptr PhysicalDeviceFeatures
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceFeatures where
  zero :: PhysicalDeviceFeatures
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceFeatures
PhysicalDeviceFeatures
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceSparseProperties - Structure specifying physical device
-- sparse memory properties
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'PhysicalDeviceProperties'
data PhysicalDeviceSparseProperties = PhysicalDeviceSparseProperties
  { -- | @residencyStandard2DBlockShape@ is 'Vulkan.Core10.FundamentalTypes.TRUE'
    -- if the physical device will access all single-sample 2D sparse resources
    -- using the standard sparse image block shapes (based on image format), as
    -- described in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory-sparseblockshapessingle Standard Sparse Image Block Shapes (Single Sample)>
    -- table. If this property is not supported the value returned in the
    -- @imageGranularity@ member of the
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties'
    -- structure for single-sample 2D images is not /required/ to match the
    -- standard sparse image block dimensions listed in the table.
    PhysicalDeviceSparseProperties -> Bool
residencyStandard2DBlockShape :: Bool
  , -- | @residencyStandard2DMultisampleBlockShape@ is
    -- 'Vulkan.Core10.FundamentalTypes.TRUE' if the physical device will access
    -- all multisample 2D sparse resources using the standard sparse image
    -- block shapes (based on image format), as described in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory-sparseblockshapesmsaa Standard Sparse Image Block Shapes (MSAA)>
    -- table. If this property is not supported, the value returned in the
    -- @imageGranularity@ member of the
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties'
    -- structure for multisample 2D images is not /required/ to match the
    -- standard sparse image block dimensions listed in the table.
    PhysicalDeviceSparseProperties -> Bool
residencyStandard2DMultisampleBlockShape :: Bool
  , -- | @residencyStandard3DBlockShape@ is 'Vulkan.Core10.FundamentalTypes.TRUE'
    -- if the physical device will access all 3D sparse resources using the
    -- standard sparse image block shapes (based on image format), as described
    -- in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory-sparseblockshapessingle Standard Sparse Image Block Shapes (Single Sample)>
    -- table. If this property is not supported, the value returned in the
    -- @imageGranularity@ member of the
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties'
    -- structure for 3D images is not /required/ to match the standard sparse
    -- image block dimensions listed in the table.
    PhysicalDeviceSparseProperties -> Bool
residencyStandard3DBlockShape :: Bool
  , -- | @residencyAlignedMipSize@ is 'Vulkan.Core10.FundamentalTypes.TRUE' if
    -- images with mip level dimensions that are not integer multiples of the
    -- corresponding dimensions of the sparse image block /may/ be placed in
    -- the mip tail. If this property is not reported, only mip levels with
    -- dimensions smaller than the @imageGranularity@ member of the
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties'
    -- structure will be placed in the mip tail. If this property is reported
    -- the implementation is allowed to return
    -- 'Vulkan.Core10.Enums.SparseImageFormatFlagBits.SPARSE_IMAGE_FORMAT_ALIGNED_MIP_SIZE_BIT'
    -- in the @flags@ member of
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties',
    -- indicating that mip level dimensions that are not integer multiples of
    -- the corresponding dimensions of the sparse image block will be placed in
    -- the mip tail.
    PhysicalDeviceSparseProperties -> Bool
residencyAlignedMipSize :: Bool
  , -- | @residencyNonResidentStrict@ specifies whether the physical device /can/
    -- consistently access non-resident regions of a resource. If this property
    -- is 'Vulkan.Core10.FundamentalTypes.TRUE', access to non-resident regions
    -- of resources will be guaranteed to return values as if the resource were
    -- populated with 0; writes to non-resident regions will be discarded.
    PhysicalDeviceSparseProperties -> Bool
residencyNonResidentStrict :: Bool
  }
  deriving (Typeable, PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> Bool
(PhysicalDeviceSparseProperties
 -> PhysicalDeviceSparseProperties -> Bool)
-> (PhysicalDeviceSparseProperties
    -> PhysicalDeviceSparseProperties -> Bool)
-> Eq PhysicalDeviceSparseProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> Bool
$c/= :: PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> Bool
== :: PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> Bool
$c== :: PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSparseProperties)
#endif
deriving instance Show PhysicalDeviceSparseProperties

instance ToCStruct PhysicalDeviceSparseProperties where
  withCStruct :: PhysicalDeviceSparseProperties
-> (Ptr PhysicalDeviceSparseProperties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceSparseProperties
x f :: Ptr PhysicalDeviceSparseProperties -> IO b
f = Int -> Int -> (Ptr PhysicalDeviceSparseProperties -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 20 4 ((Ptr PhysicalDeviceSparseProperties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceSparseProperties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceSparseProperties
p -> Ptr PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSparseProperties
p PhysicalDeviceSparseProperties
x (Ptr PhysicalDeviceSparseProperties -> IO b
f Ptr PhysicalDeviceSparseProperties
p)
  pokeCStruct :: Ptr PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceSparseProperties
p PhysicalDeviceSparseProperties{..} f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
residencyStandard2DBlockShape))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
residencyStandard2DMultisampleBlockShape))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
residencyStandard3DBlockShape))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
residencyAlignedMipSize))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
residencyNonResidentStrict))
    IO b
f
  cStructSize :: Int
cStructSize = 20
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr PhysicalDeviceSparseProperties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceSparseProperties
p f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> 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 PhysicalDeviceSparseProperties where
  peekCStruct :: Ptr PhysicalDeviceSparseProperties
-> IO PhysicalDeviceSparseProperties
peekCStruct p :: Ptr PhysicalDeviceSparseProperties
p = do
    Bool32
residencyStandard2DBlockShape <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32))
    Bool32
residencyStandard2DMultisampleBlockShape <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Bool32))
    Bool32
residencyStandard3DBlockShape <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Bool32))
    Bool32
residencyAlignedMipSize <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Bool32))
    Bool32
residencyNonResidentStrict <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSparseProperties
p Ptr PhysicalDeviceSparseProperties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceSparseProperties -> IO PhysicalDeviceSparseProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceSparseProperties
 -> IO PhysicalDeviceSparseProperties)
-> PhysicalDeviceSparseProperties
-> IO PhysicalDeviceSparseProperties
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool -> Bool -> Bool -> Bool -> PhysicalDeviceSparseProperties
PhysicalDeviceSparseProperties
             (Bool32 -> Bool
bool32ToBool Bool32
residencyStandard2DBlockShape) (Bool32 -> Bool
bool32ToBool Bool32
residencyStandard2DMultisampleBlockShape) (Bool32 -> Bool
bool32ToBool Bool32
residencyStandard3DBlockShape) (Bool32 -> Bool
bool32ToBool Bool32
residencyAlignedMipSize) (Bool32 -> Bool
bool32ToBool Bool32
residencyNonResidentStrict)

instance Storable PhysicalDeviceSparseProperties where
  sizeOf :: PhysicalDeviceSparseProperties -> Int
sizeOf ~PhysicalDeviceSparseProperties
_ = 20
  alignment :: PhysicalDeviceSparseProperties -> Int
alignment ~PhysicalDeviceSparseProperties
_ = 4
  peek :: Ptr PhysicalDeviceSparseProperties
-> IO PhysicalDeviceSparseProperties
peek = Ptr PhysicalDeviceSparseProperties
-> IO PhysicalDeviceSparseProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO ()
poke ptr :: Ptr PhysicalDeviceSparseProperties
ptr poked :: PhysicalDeviceSparseProperties
poked = Ptr PhysicalDeviceSparseProperties
-> PhysicalDeviceSparseProperties -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSparseProperties
ptr PhysicalDeviceSparseProperties
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceSparseProperties where
  zero :: PhysicalDeviceSparseProperties
zero = Bool
-> Bool -> Bool -> Bool -> Bool -> PhysicalDeviceSparseProperties
PhysicalDeviceSparseProperties
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceLimits - Structure reporting implementation-dependent
-- physical device limits
--
-- = Members
--
-- The 'PhysicalDeviceLimits' are properties of the physical device. These
-- are available in the @limits@ member of the 'PhysicalDeviceProperties'
-- structure which is returned from 'getPhysicalDeviceProperties'.
--
-- = Description
--
-- [1]
--     For all bitmasks of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits', the
--     sample count limits defined above represent the minimum supported
--     sample counts for each image type. Individual images /may/ support
--     additional sample counts, which are queried using
--     'getPhysicalDeviceImageFormatProperties' as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-supported-sample-counts Supported Sample Counts>.
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize', 'PhysicalDeviceProperties',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlags'
data PhysicalDeviceLimits = PhysicalDeviceLimits
  { -- | @maxImageDimension1D@ is the largest dimension (@width@) that is
    -- guaranteed to be supported for all images created with an @imageType@ of
    -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D'. Some combinations of
    -- image parameters (format, usage, etc.) /may/ allow support for larger
    -- dimensions, which /can/ be queried using
    -- 'getPhysicalDeviceImageFormatProperties'.
    PhysicalDeviceLimits -> Word32
maxImageDimension1D :: Word32
  , -- | @maxImageDimension2D@ is the largest dimension (@width@ or @height@)
    -- that is guaranteed to be supported for all images created with an
    -- @imageType@ of 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and without
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CUBE_COMPATIBLE_BIT'
    -- set in @flags@. Some combinations of image parameters (format, usage,
    -- etc.) /may/ allow support for larger dimensions, which /can/ be queried
    -- using 'getPhysicalDeviceImageFormatProperties'.
    PhysicalDeviceLimits -> Word32
maxImageDimension2D :: Word32
  , -- | @maxImageDimension3D@ is the largest dimension (@width@, @height@, or
    -- @depth@) that is guaranteed to be supported for all images created with
    -- an @imageType@ of 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D'. Some
    -- combinations of image parameters (format, usage, etc.) /may/ allow
    -- support for larger dimensions, which /can/ be queried using
    -- 'getPhysicalDeviceImageFormatProperties'.
    PhysicalDeviceLimits -> Word32
maxImageDimension3D :: Word32
  , -- | @maxImageDimensionCube@ is the largest dimension (@width@ or @height@)
    -- that is guaranteed to be supported for all images created with an
    -- @imageType@ of 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' and with
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CUBE_COMPATIBLE_BIT'
    -- set in @flags@. Some combinations of image parameters (format, usage,
    -- etc.) /may/ allow support for larger dimensions, which /can/ be queried
    -- using 'getPhysicalDeviceImageFormatProperties'.
    PhysicalDeviceLimits -> Word32
maxImageDimensionCube :: Word32
  , -- | @maxImageArrayLayers@ is the maximum number of layers (@arrayLayers@)
    -- for an image.
    PhysicalDeviceLimits -> Word32
maxImageArrayLayers :: Word32
  , -- | @maxTexelBufferElements@ is the maximum number of addressable texels for
    -- a buffer view created on a buffer which was created with the
    -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_UNIFORM_TEXEL_BUFFER_BIT'
    -- or
    -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_STORAGE_TEXEL_BUFFER_BIT'
    -- set in the @usage@ member of the 'Vulkan.Core10.Buffer.BufferCreateInfo'
    -- structure.
    PhysicalDeviceLimits -> Word32
maxTexelBufferElements :: Word32
  , -- | @maxUniformBufferRange@ is the maximum value that /can/ be specified in
    -- the @range@ member of any
    -- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo' structures passed to
    -- a call to 'Vulkan.Core10.DescriptorSet.updateDescriptorSets' for
    -- descriptors of type
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'.
    PhysicalDeviceLimits -> Word32
maxUniformBufferRange :: Word32
  , -- | @maxStorageBufferRange@ is the maximum value that /can/ be specified in
    -- the @range@ member of any
    -- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo' structures passed to
    -- a call to 'Vulkan.Core10.DescriptorSet.updateDescriptorSets' for
    -- descriptors of type
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'.
    PhysicalDeviceLimits -> Word32
maxStorageBufferRange :: Word32
  , -- | @maxPushConstantsSize@ is the maximum size, in bytes, of the pool of
    -- push constant memory. For each of the push constant ranges indicated by
    -- the @pPushConstantRanges@ member of the
    -- 'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo' structure,
    -- (@offset@ + @size@) /must/ be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxPushConstantsSize :: Word32
  , -- | @maxMemoryAllocationCount@ is the maximum number of device memory
    -- allocations, as created by 'Vulkan.Core10.Memory.allocateMemory', which
    -- /can/ simultaneously exist.
    PhysicalDeviceLimits -> Word32
maxMemoryAllocationCount :: Word32
  , -- | @maxSamplerAllocationCount@ is the maximum number of sampler objects, as
    -- created by 'Vulkan.Core10.Sampler.createSampler', which /can/
    -- simultaneously exist on a device.
    PhysicalDeviceLimits -> Word32
maxSamplerAllocationCount :: Word32
  , -- | @bufferImageGranularity@ is the granularity, in bytes, at which buffer
    -- or linear image resources, and optimal image resources /can/ be bound to
    -- adjacent offsets in the same 'Vulkan.Core10.Handles.DeviceMemory' object
    -- without aliasing. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-bufferimagegranularity Buffer-Image Granularity>
    -- for more details.
    PhysicalDeviceLimits -> DeviceSize
bufferImageGranularity :: DeviceSize
  , -- | @sparseAddressSpaceSize@ is the total amount of address space available,
    -- in bytes, for sparse memory resources. This is an upper bound on the sum
    -- of the size of all sparse resources, regardless of whether any memory is
    -- bound to them.
    PhysicalDeviceLimits -> DeviceSize
sparseAddressSpaceSize :: DeviceSize
  , -- | @maxBoundDescriptorSets@ is the maximum number of descriptor sets that
    -- /can/ be simultaneously used by a pipeline. All
    -- 'Vulkan.Core10.Handles.DescriptorSet' decorations in shader modules
    -- /must/ have a value less than @maxBoundDescriptorSets@. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sets>.
    PhysicalDeviceLimits -> Word32
maxBoundDescriptorSets :: Word32
  , -- | @maxPerStageDescriptorSamplers@ is the maximum number of samplers that
    -- /can/ be accessible to a single shader stage in a pipeline layout.
    -- Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a shader
    -- stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampler>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-combinedimagesampler>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorSamplers :: Word32
  , -- | @maxPerStageDescriptorUniformBuffers@ is the maximum number of uniform
    -- buffers that /can/ be accessible to a single shader stage in a pipeline
    -- layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a shader
    -- stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformbuffer>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformbufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorUniformBuffers :: Word32
  , -- | @maxPerStageDescriptorStorageBuffers@ is the maximum number of storage
    -- buffers that /can/ be accessible to a single shader stage in a pipeline
    -- layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a
    -- pipeline shader stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagebuffer>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagebufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorStorageBuffers :: Word32
  , -- | @maxPerStageDescriptorSampledImages@ is the maximum number of sampled
    -- images that /can/ be accessible to a single shader stage in a pipeline
    -- layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a
    -- pipeline shader stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-combinedimagesampler>,
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampledimage>,
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformtexelbuffer>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorSampledImages :: Word32
  , -- | @maxPerStageDescriptorStorageImages@ is the maximum number of storage
    -- images that /can/ be accessible to a single shader stage in a pipeline
    -- layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a
    -- pipeline shader stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storageimage>,
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagetexelbuffer>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorStorageImages :: Word32
  , -- | @maxPerStageDescriptorInputAttachments@ is the maximum number of input
    -- attachments that /can/ be accessible to a single shader stage in a
    -- pipeline layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. A descriptor is accessible to a
    -- pipeline shader stage when the @stageFlags@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding' structure has
    -- the bit for that shader stage set. These are only supported for the
    -- fragment stage. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-inputattachment>.
    PhysicalDeviceLimits -> Word32
maxPerStageDescriptorInputAttachments :: Word32
  , -- | @maxPerStageResources@ is the maximum number of resources that /can/ be
    -- accessible to a single shader stage in a pipeline layout. Descriptors
    -- with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC',
    -- or 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. For the fragment shader stage the
    -- framebuffer color attachments also count against this limit.
    PhysicalDeviceLimits -> Word32
maxPerStageResources :: Word32
  , -- | @maxDescriptorSetSamplers@ is the maximum number of samplers that /can/
    -- be included in a pipeline layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampler>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-combinedimagesampler>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetSamplers :: Word32
  , -- | @maxDescriptorSetUniformBuffers@ is the maximum number of uniform
    -- buffers that /can/ be included in a pipeline layout. Descriptors with a
    -- type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformbuffer>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformbufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetUniformBuffers :: Word32
  , -- | @maxDescriptorSetUniformBuffersDynamic@ is the maximum number of dynamic
    -- uniform buffers that /can/ be included in a pipeline layout. Descriptors
    -- with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformbufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetUniformBuffersDynamic :: Word32
  , -- | @maxDescriptorSetStorageBuffers@ is the maximum number of storage
    -- buffers that /can/ be included in a pipeline layout. Descriptors with a
    -- type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagebuffer>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagebufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetStorageBuffers :: Word32
  , -- | @maxDescriptorSetStorageBuffersDynamic@ is the maximum number of dynamic
    -- storage buffers that /can/ be included in a pipeline layout. Descriptors
    -- with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagebufferdynamic>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetStorageBuffersDynamic :: Word32
  , -- | @maxDescriptorSetSampledImages@ is the maximum number of sampled images
    -- that /can/ be included in a pipeline layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-combinedimagesampler>,
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampledimage>,
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-uniformtexelbuffer>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetSampledImages :: Word32
  , -- | @maxDescriptorSetStorageImages@ is the maximum number of storage images
    -- that /can/ be included in a pipeline layout. Descriptors with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storageimage>,
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storagetexelbuffer>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetStorageImages :: Word32
  , -- | @maxDescriptorSetInputAttachments@ is the maximum number of input
    -- attachments that /can/ be included in a pipeline layout. Descriptors
    -- with a type of
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
    -- count against this limit. Only descriptors in descriptor set layouts
    -- created without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set count against this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-inputattachment>.
    PhysicalDeviceLimits -> Word32
maxDescriptorSetInputAttachments :: Word32
  , -- | @maxVertexInputAttributes@ is the maximum number of vertex input
    -- attributes that /can/ be specified for a graphics pipeline. These are
    -- described in the array of
    -- 'Vulkan.Core10.Pipeline.VertexInputAttributeDescription' structures that
    -- are provided at graphics pipeline creation time via the
    -- @pVertexAttributeDescriptions@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineVertexInputStateCreateInfo' structure.
    -- See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-attrib>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>.
    PhysicalDeviceLimits -> Word32
maxVertexInputAttributes :: Word32
  , -- | @maxVertexInputBindings@ is the maximum number of vertex buffers that
    -- /can/ be specified for providing vertex attributes to a graphics
    -- pipeline. These are described in the array of
    -- 'Vulkan.Core10.Pipeline.VertexInputBindingDescription' structures that
    -- are provided at graphics pipeline creation time via the
    -- @pVertexBindingDescriptions@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineVertexInputStateCreateInfo' structure.
    -- The @binding@ member of
    -- 'Vulkan.Core10.Pipeline.VertexInputBindingDescription' /must/ be less
    -- than this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>.
    PhysicalDeviceLimits -> Word32
maxVertexInputBindings :: Word32
  , -- | @maxVertexInputAttributeOffset@ is the maximum vertex input attribute
    -- offset that /can/ be added to the vertex input binding stride. The
    -- @offset@ member of the
    -- 'Vulkan.Core10.Pipeline.VertexInputAttributeDescription' structure
    -- /must/ be less than or equal to this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>.
    PhysicalDeviceLimits -> Word32
maxVertexInputAttributeOffset :: Word32
  , -- | @maxVertexInputBindingStride@ is the maximum vertex input binding stride
    -- that /can/ be specified in a vertex input binding. The @stride@ member
    -- of the 'Vulkan.Core10.Pipeline.VertexInputBindingDescription' structure
    -- /must/ be less than or equal to this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input>.
    PhysicalDeviceLimits -> Word32
maxVertexInputBindingStride :: Word32
  , -- | @maxVertexOutputComponents@ is the maximum number of components of
    -- output variables which /can/ be output by a vertex shader. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-vertex>.
    PhysicalDeviceLimits -> Word32
maxVertexOutputComponents :: Word32
  , -- | @maxTessellationGenerationLevel@ is the maximum tessellation generation
    -- level supported by the fixed-function tessellation primitive generator.
    -- See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#tessellation>.
    PhysicalDeviceLimits -> Word32
maxTessellationGenerationLevel :: Word32
  , -- | @maxTessellationPatchSize@ is the maximum patch size, in vertices, of
    -- patches that /can/ be processed by the tessellation control shader and
    -- tessellation primitive generator. The @patchControlPoints@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineTessellationStateCreateInfo' structure
    -- specified at pipeline creation time and the value provided in the
    -- @OutputVertices@ execution mode of shader modules /must/ be less than or
    -- equal to this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#tessellation>.
    PhysicalDeviceLimits -> Word32
maxTessellationPatchSize :: Word32
  , -- | @maxTessellationControlPerVertexInputComponents@ is the maximum number
    -- of components of input variables which /can/ be provided as per-vertex
    -- inputs to the tessellation control shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationControlPerVertexInputComponents :: Word32
  , -- | @maxTessellationControlPerVertexOutputComponents@ is the maximum number
    -- of components of per-vertex output variables which /can/ be output from
    -- the tessellation control shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationControlPerVertexOutputComponents :: Word32
  , -- | @maxTessellationControlPerPatchOutputComponents@ is the maximum number
    -- of components of per-patch output variables which /can/ be output from
    -- the tessellation control shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationControlPerPatchOutputComponents :: Word32
  , -- | @maxTessellationControlTotalOutputComponents@ is the maximum total
    -- number of components of per-vertex and per-patch output variables which
    -- /can/ be output from the tessellation control shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationControlTotalOutputComponents :: Word32
  , -- | @maxTessellationEvaluationInputComponents@ is the maximum number of
    -- components of input variables which /can/ be provided as per-vertex
    -- inputs to the tessellation evaluation shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationEvaluationInputComponents :: Word32
  , -- | @maxTessellationEvaluationOutputComponents@ is the maximum number of
    -- components of per-vertex output variables which /can/ be output from the
    -- tessellation evaluation shader stage.
    PhysicalDeviceLimits -> Word32
maxTessellationEvaluationOutputComponents :: Word32
  , -- | @maxGeometryShaderInvocations@ is the maximum invocation count supported
    -- for instanced geometry shaders. The value provided in the @Invocations@
    -- execution mode of shader modules /must/ be less than or equal to this
    -- limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#geometry>.
    PhysicalDeviceLimits -> Word32
maxGeometryShaderInvocations :: Word32
  , -- | @maxGeometryInputComponents@ is the maximum number of components of
    -- input variables which /can/ be provided as inputs to the geometry shader
    -- stage.
    PhysicalDeviceLimits -> Word32
maxGeometryInputComponents :: Word32
  , -- | @maxGeometryOutputComponents@ is the maximum number of components of
    -- output variables which /can/ be output from the geometry shader stage.
    PhysicalDeviceLimits -> Word32
maxGeometryOutputComponents :: Word32
  , -- | @maxGeometryOutputVertices@ is the maximum number of vertices which
    -- /can/ be emitted by any geometry shader.
    PhysicalDeviceLimits -> Word32
maxGeometryOutputVertices :: Word32
  , -- | @maxGeometryTotalOutputComponents@ is the maximum total number of
    -- components of output, across all emitted vertices, which /can/ be output
    -- from the geometry shader stage.
    PhysicalDeviceLimits -> Word32
maxGeometryTotalOutputComponents :: Word32
  , -- | @maxFragmentInputComponents@ is the maximum number of components of
    -- input variables which /can/ be provided as inputs to the fragment shader
    -- stage.
    PhysicalDeviceLimits -> Word32
maxFragmentInputComponents :: Word32
  , -- | @maxFragmentOutputAttachments@ is the maximum number of output
    -- attachments which /can/ be written to by the fragment shader stage.
    PhysicalDeviceLimits -> Word32
maxFragmentOutputAttachments :: Word32
  , -- | @maxFragmentDualSrcAttachments@ is the maximum number of output
    -- attachments which /can/ be written to by the fragment shader stage when
    -- blending is enabled and one of the dual source blend modes is in use.
    -- See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-dsb>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dualSrcBlend dualSrcBlend>.
    PhysicalDeviceLimits -> Word32
maxFragmentDualSrcAttachments :: Word32
  , -- | @maxFragmentCombinedOutputResources@ is the total number of storage
    -- buffers, storage images, and output @Location@ decorated color
    -- attachments (described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-fragmentoutput Fragment Output Interface>)
    -- which /can/ be used in the fragment shader stage.
    PhysicalDeviceLimits -> Word32
maxFragmentCombinedOutputResources :: Word32
  , -- | @maxComputeSharedMemorySize@ is the maximum total storage size, in
    -- bytes, available for variables declared with the @Workgroup@ storage
    -- class in shader modules (or with the @shared@ storage qualifier in GLSL)
    -- in the compute shader stage. The amount of storage consumed by the
    -- variables declared with the @Workgroup@ storage class is
    -- implementation-dependent. However, the amount of storage consumed may
    -- not exceed the largest block size that would be obtained if all active
    -- variables declared with @Workgroup@ storage class were assigned offsets
    -- in an arbitrary order by successively taking the smallest valid offset
    -- according to the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-resources-standard-layout Standard Storage Buffer Layout>
    -- rules. (This is equivalent to using the GLSL std430 layout rules.)
    PhysicalDeviceLimits -> Word32
maxComputeSharedMemorySize :: Word32
  , -- | @maxComputeWorkGroupCount@[3] is the maximum number of local workgroups
    -- that /can/ be dispatched by a single dispatch command. These three
    -- values represent the maximum number of local workgroups for the X, Y,
    -- and Z dimensions, respectively. The workgroup count parameters to the
    -- dispatch commands /must/ be less than or equal to the corresponding
    -- limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#dispatch>.
    PhysicalDeviceLimits -> (Word32, Word32, Word32)
maxComputeWorkGroupCount :: (Word32, Word32, Word32)
  , -- | @maxComputeWorkGroupInvocations@ is the maximum total number of compute
    -- shader invocations in a single local workgroup. The product of the X, Y,
    -- and Z sizes, as specified by the @LocalSize@ execution mode in shader
    -- modules or by the object decorated by the @WorkgroupSize@ decoration,
    -- /must/ be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxComputeWorkGroupInvocations :: Word32
  , -- | @maxComputeWorkGroupSize@[3] is the maximum size of a local compute
    -- workgroup, per dimension. These three values represent the maximum local
    -- workgroup size in the X, Y, and Z dimensions, respectively. The @x@,
    -- @y@, and @z@ sizes, as specified by the @LocalSize@ execution mode or by
    -- the object decorated by the @WorkgroupSize@ decoration in shader
    -- modules, /must/ be less than or equal to the corresponding limit.
    PhysicalDeviceLimits -> (Word32, Word32, Word32)
maxComputeWorkGroupSize :: (Word32, Word32, Word32)
  , -- | @subPixelPrecisionBits@ is the number of bits of subpixel precision in
    -- framebuffer coordinates xf and yf. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast>.
    PhysicalDeviceLimits -> Word32
subPixelPrecisionBits :: Word32
  , -- | @subTexelPrecisionBits@ is the number of bits of precision in the
    -- division along an axis of an image used for minification and
    -- magnification filters. 2@subTexelPrecisionBits@ is the actual number of
    -- divisions along each axis of the image represented. Sub-texel values
    -- calculated during image sampling will snap to these locations when
    -- generating the filtered results.
    PhysicalDeviceLimits -> Word32
subTexelPrecisionBits :: Word32
  , -- | @mipmapPrecisionBits@ is the number of bits of division that the LOD
    -- calculation for mipmap fetching get snapped to when determining the
    -- contribution from each mip level to the mip filtered results.
    -- 2@mipmapPrecisionBits@ is the actual number of divisions.
    PhysicalDeviceLimits -> Word32
mipmapPrecisionBits :: Word32
  , -- | @maxDrawIndexedIndexValue@ is the maximum index value that /can/ be used
    -- for indexed draw calls when using 32-bit indices. This excludes the
    -- primitive restart index value of 0xFFFFFFFF. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fullDrawIndexUint32 fullDrawIndexUint32>.
    PhysicalDeviceLimits -> Word32
maxDrawIndexedIndexValue :: Word32
  , -- | @maxDrawIndirectCount@ is the maximum draw count that is supported for
    -- indirect draw calls. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multiDrawIndirect>.
    PhysicalDeviceLimits -> Word32
maxDrawIndirectCount :: Word32
  , -- | @maxSamplerLodBias@ is the maximum absolute sampler LOD bias. The sum of
    -- the @mipLodBias@ member of the 'Vulkan.Core10.Sampler.SamplerCreateInfo'
    -- structure and the @Bias@ operand of image sampling operations in shader
    -- modules (or 0 if no @Bias@ operand is provided to an image sampling
    -- operation) are clamped to the range
    -- [-@maxSamplerLodBias@,+@maxSamplerLodBias@]. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-mipLodBias>.
    PhysicalDeviceLimits -> Float
maxSamplerLodBias :: Float
  , -- | @maxSamplerAnisotropy@ is the maximum degree of sampler anisotropy. The
    -- maximum degree of anisotropic filtering used for an image sampling
    -- operation is the minimum of the @maxAnisotropy@ member of the
    -- 'Vulkan.Core10.Sampler.SamplerCreateInfo' structure and this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-maxAnisotropy>.
    PhysicalDeviceLimits -> Float
maxSamplerAnisotropy :: Float
  , -- | @maxViewports@ is the maximum number of active viewports. The
    -- @viewportCount@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' structure that
    -- is provided at pipeline creation /must/ be less than or equal to this
    -- limit.
    PhysicalDeviceLimits -> Word32
maxViewports :: Word32
  , -- | @maxViewportDimensions@[2] are the maximum viewport dimensions in the X
    -- (width) and Y (height) dimensions, respectively. The maximum viewport
    -- dimensions /must/ be greater than or equal to the largest image which
    -- /can/ be created and used as a framebuffer attachment. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-viewport Controlling the Viewport>.
    PhysicalDeviceLimits -> (Word32, Word32)
maxViewportDimensions :: (Word32, Word32)
  , -- | @viewportBoundsRange@[2] is the [minimum, maximum] range that the
    -- corners of a viewport /must/ be contained in. This range /must/ be at
    -- least [-2 × @size@, 2 × @size@ - 1], where @size@ =
    -- max(@maxViewportDimensions@[0], @maxViewportDimensions@[1]). See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-viewport Controlling the Viewport>.
    --
    -- Note
    --
    -- The intent of the @viewportBoundsRange@ limit is to allow a maximum
    -- sized viewport to be arbitrarily shifted relative to the output target
    -- as long as at least some portion intersects. This would give a bounds
    -- limit of [-@size@ + 1, 2 × @size@ - 1] which would allow all possible
    -- non-empty-set intersections of the output target and the viewport. Since
    -- these numbers are typically powers of two, picking the signed number
    -- range using the smallest possible number of bits ends up with the
    -- specified range.
    PhysicalDeviceLimits -> (Float, Float)
viewportBoundsRange :: (Float, Float)
  , -- | @viewportSubPixelBits@ is the number of bits of subpixel precision for
    -- viewport bounds. The subpixel precision that floating-point viewport
    -- bounds are interpreted at is given by this limit.
    PhysicalDeviceLimits -> Word32
viewportSubPixelBits :: Word32
  , -- | @minMemoryMapAlignment@ is the minimum /required/ alignment, in bytes,
    -- of host visible memory allocations within the host address space. When
    -- mapping a memory allocation with 'Vulkan.Core10.Memory.mapMemory',
    -- subtracting @offset@ bytes from the returned pointer will always produce
    -- an integer multiple of this limit. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-device-hostaccess>.
    PhysicalDeviceLimits -> DeviceSize
minMemoryMapAlignment :: Word64
  , -- | @minTexelBufferOffsetAlignment@ is the minimum /required/ alignment, in
    -- bytes, for the @offset@ member of the
    -- 'Vulkan.Core10.BufferView.BufferViewCreateInfo' structure for texel
    -- buffers. If
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-texelBufferAlignment texelBufferAlignment>
    -- is enabled, this limit is equivalent to the maximum of the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-uniformTexelBufferOffsetAlignmentBytes uniformTexelBufferOffsetAlignmentBytes>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-storageTexelBufferOffsetAlignmentBytes storageTexelBufferOffsetAlignmentBytes>
    -- members of
    -- 'Vulkan.Extensions.VK_EXT_texel_buffer_alignment.PhysicalDeviceTexelBufferAlignmentPropertiesEXT',
    -- but smaller alignment is optionally: allowed by
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-storageTexelBufferOffsetSingleTexelAlignment storageTexelBufferOffsetSingleTexelAlignment>
    -- and
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-uniformTexelBufferOffsetSingleTexelAlignment uniformTexelBufferOffsetSingleTexelAlignment>.
    -- If
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-texelBufferAlignment texelBufferAlignment>
    -- is not enabled,
    -- 'Vulkan.Core10.BufferView.BufferViewCreateInfo'::@offset@ /must/ be a
    -- multiple of this value.
    PhysicalDeviceLimits -> DeviceSize
minTexelBufferOffsetAlignment :: DeviceSize
  , -- | @minUniformBufferOffsetAlignment@ is the minimum /required/ alignment,
    -- in bytes, for the @offset@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo' structure for uniform
    -- buffers. When a descriptor of type
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
    -- is updated, the @offset@ /must/ be an integer multiple of this limit.
    -- Similarly, dynamic offsets for uniform buffers /must/ be multiples of
    -- this limit.
    PhysicalDeviceLimits -> DeviceSize
minUniformBufferOffsetAlignment :: DeviceSize
  , -- | @minStorageBufferOffsetAlignment@ is the minimum /required/ alignment,
    -- in bytes, for the @offset@ member of the
    -- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo' structure for storage
    -- buffers. When a descriptor of type
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' or
    -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
    -- is updated, the @offset@ /must/ be an integer multiple of this limit.
    -- Similarly, dynamic offsets for storage buffers /must/ be multiples of
    -- this limit.
    PhysicalDeviceLimits -> DeviceSize
minStorageBufferOffsetAlignment :: DeviceSize
  , -- | @minTexelOffset@ is the minimum offset value for the @ConstOffset@ image
    -- operand of any of the @OpImageSample@* or @OpImageFetch@* image
    -- instructions.
    PhysicalDeviceLimits -> Int32
minTexelOffset :: Int32
  , -- | @maxTexelOffset@ is the maximum offset value for the @ConstOffset@ image
    -- operand of any of the @OpImageSample@* or @OpImageFetch@* image
    -- instructions.
    PhysicalDeviceLimits -> Word32
maxTexelOffset :: Word32
  , -- | @minTexelGatherOffset@ is the minimum offset value for the @Offset@,
    -- @ConstOffset@, or @ConstOffsets@ image operands of any of the
    -- @OpImage@*@Gather@ image instructions.
    PhysicalDeviceLimits -> Int32
minTexelGatherOffset :: Int32
  , -- | @maxTexelGatherOffset@ is the maximum offset value for the @Offset@,
    -- @ConstOffset@, or @ConstOffsets@ image operands of any of the
    -- @OpImage@*@Gather@ image instructions.
    PhysicalDeviceLimits -> Word32
maxTexelGatherOffset :: Word32
  , -- | @minInterpolationOffset@ is the minimum negative offset value for the
    -- @offset@ operand of the @InterpolateAtOffset@ extended instruction.
    PhysicalDeviceLimits -> Float
minInterpolationOffset :: Float
  , -- | @maxInterpolationOffset@ is the maximum positive offset value for the
    -- @offset@ operand of the @InterpolateAtOffset@ extended instruction.
    PhysicalDeviceLimits -> Float
maxInterpolationOffset :: Float
  , -- | @subPixelInterpolationOffsetBits@ is the number of subpixel fractional
    -- bits that the @x@ and @y@ offsets to the @InterpolateAtOffset@ extended
    -- instruction /may/ be rounded to as fixed-point values.
    PhysicalDeviceLimits -> Word32
subPixelInterpolationOffsetBits :: Word32
  , -- | @maxFramebufferWidth@ is the maximum width for a framebuffer. The
    -- @width@ member of the 'Vulkan.Core10.Pass.FramebufferCreateInfo'
    -- structure /must/ be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxFramebufferWidth :: Word32
  , -- | @maxFramebufferHeight@ is the maximum height for a framebuffer. The
    -- @height@ member of the 'Vulkan.Core10.Pass.FramebufferCreateInfo'
    -- structure /must/ be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxFramebufferHeight :: Word32
  , -- | @maxFramebufferLayers@ is the maximum layer count for a layered
    -- framebuffer. The @layers@ member of the
    -- 'Vulkan.Core10.Pass.FramebufferCreateInfo' structure /must/ be less than
    -- or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxFramebufferLayers :: Word32
  , -- | @framebufferColorSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the color sample counts that are supported for all framebuffer color
    -- attachments with floating- or fixed-point formats. There is no limit
    -- that specifies the color sample counts that are supported for all color
    -- attachments with integer formats.
    PhysicalDeviceLimits -> SampleCountFlags
framebufferColorSampleCounts :: SampleCountFlags
  , -- | @framebufferDepthSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the supported depth sample counts for all framebuffer depth\/stencil
    -- attachments, when the format includes a depth component.
    PhysicalDeviceLimits -> SampleCountFlags
framebufferDepthSampleCounts :: SampleCountFlags
  , -- | @framebufferStencilSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the supported stencil sample counts for all framebuffer depth\/stencil
    -- attachments, when the format includes a stencil component.
    PhysicalDeviceLimits -> SampleCountFlags
framebufferStencilSampleCounts :: SampleCountFlags
  , -- | @framebufferNoAttachmentsSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the supported sample counts for a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments subpass which uses no attachments>.
    PhysicalDeviceLimits -> SampleCountFlags
framebufferNoAttachmentsSampleCounts :: SampleCountFlags
  , -- | @maxColorAttachments@ is the maximum number of color attachments that
    -- /can/ be used by a subpass in a render pass. The @colorAttachmentCount@
    -- member of the 'Vulkan.Core10.Pass.SubpassDescription' structure /must/
    -- be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxColorAttachments :: Word32
  , -- | @sampledImageColorSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the sample counts supported for all 2D images created with
    -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL', @usage@
    -- containing
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', and a
    -- non-integer color format.
    PhysicalDeviceLimits -> SampleCountFlags
sampledImageColorSampleCounts :: SampleCountFlags
  , -- | @sampledImageIntegerSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the sample counts supported for all 2D images created with
    -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL', @usage@
    -- containing
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', and an
    -- integer color format.
    PhysicalDeviceLimits -> SampleCountFlags
sampledImageIntegerSampleCounts :: SampleCountFlags
  , -- | @sampledImageDepthSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the sample counts supported for all 2D images created with
    -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL', @usage@
    -- containing
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', and a
    -- depth format.
    PhysicalDeviceLimits -> SampleCountFlags
sampledImageDepthSampleCounts :: SampleCountFlags
  , -- | @sampledImageStencilSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the sample supported for all 2D images created with
    -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL', @usage@
    -- containing
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', and a
    -- stencil format.
    PhysicalDeviceLimits -> SampleCountFlags
sampledImageStencilSampleCounts :: SampleCountFlags
  , -- | @storageImageSampleCounts@ is a bitmask1 of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the sample counts supported for all 2D images created with
    -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL', and @usage@
    -- containing
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_STORAGE_BIT'.
    PhysicalDeviceLimits -> SampleCountFlags
storageImageSampleCounts :: SampleCountFlags
  , -- | @maxSampleMaskWords@ is the maximum number of array elements of a
    -- variable decorated with the 'Vulkan.Core10.FundamentalTypes.SampleMask'
    -- built-in decoration.
    PhysicalDeviceLimits -> Word32
maxSampleMaskWords :: Word32
  , -- | @timestampComputeAndGraphics@ specifies support for timestamps on all
    -- graphics and compute queues. If this limit is set to
    -- 'Vulkan.Core10.FundamentalTypes.TRUE', all queues that advertise the
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT' in the
    -- 'QueueFamilyProperties'::@queueFlags@ support
    -- 'QueueFamilyProperties'::@timestampValidBits@ of at least 36. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-timestamps Timestamp Queries>.
    PhysicalDeviceLimits -> Bool
timestampComputeAndGraphics :: Bool
  , -- | @timestampPeriod@ is the number of nanoseconds /required/ for a
    -- timestamp query to be incremented by 1. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-timestamps Timestamp Queries>.
    PhysicalDeviceLimits -> Float
timestampPeriod :: Float
  , -- | @maxClipDistances@ is the maximum number of clip distances that /can/ be
    -- used in a single shader stage. The size of any array declared with the
    -- @ClipDistance@ built-in decoration in a shader module /must/ be less
    -- than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxClipDistances :: Word32
  , -- | @maxCullDistances@ is the maximum number of cull distances that /can/ be
    -- used in a single shader stage. The size of any array declared with the
    -- @CullDistance@ built-in decoration in a shader module /must/ be less
    -- than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxCullDistances :: Word32
  , -- | @maxCombinedClipAndCullDistances@ is the maximum combined number of clip
    -- and cull distances that /can/ be used in a single shader stage. The sum
    -- of the sizes of any pair of arrays declared with the @ClipDistance@ and
    -- @CullDistance@ built-in decoration used by a single shader stage in a
    -- shader module /must/ be less than or equal to this limit.
    PhysicalDeviceLimits -> Word32
maxCombinedClipAndCullDistances :: Word32
  , -- | @discreteQueuePriorities@ is the number of discrete priorities that
    -- /can/ be assigned to a queue based on the value of each member of
    -- 'Vulkan.Core10.Device.DeviceQueueCreateInfo'::@pQueuePriorities@. This
    -- /must/ be at least 2, and levels /must/ be spread evenly over the range,
    -- with at least one level at 1.0, and another at 0.0. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-priority>.
    PhysicalDeviceLimits -> Word32
discreteQueuePriorities :: Word32
  , -- | @pointSizeRange@[2] is the range [@minimum@,@maximum@] of supported
    -- sizes for points. Values written to variables decorated with the
    -- @PointSize@ built-in decoration are clamped to this range.
    PhysicalDeviceLimits -> (Float, Float)
pointSizeRange :: (Float, Float)
  , -- | @lineWidthRange@[2] is the range [@minimum@,@maximum@] of supported
    -- widths for lines. Values specified by the @lineWidth@ member of the
    -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' or the
    -- @lineWidth@ parameter to
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdSetLineWidth' are clamped to
    -- this range.
    PhysicalDeviceLimits -> (Float, Float)
lineWidthRange :: (Float, Float)
  , -- | @pointSizeGranularity@ is the granularity of supported point sizes. Not
    -- all point sizes in the range defined by @pointSizeRange@ are supported.
    -- This limit specifies the granularity (or increment) between successive
    -- supported point sizes.
    PhysicalDeviceLimits -> Float
pointSizeGranularity :: Float
  , -- | @lineWidthGranularity@ is the granularity of supported line widths. Not
    -- all line widths in the range defined by @lineWidthRange@ are supported.
    -- This limit specifies the granularity (or increment) between successive
    -- supported line widths.
    PhysicalDeviceLimits -> Float
lineWidthGranularity :: Float
  , -- | @strictLines@ specifies whether lines are rasterized according to the
    -- preferred method of rasterization. If set to
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', lines /may/ be rasterized under
    -- a relaxed set of rules. If set to 'Vulkan.Core10.FundamentalTypes.TRUE',
    -- lines are rasterized as per the strict definition. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-basic Basic Line Segment Rasterization>.
    PhysicalDeviceLimits -> Bool
strictLines :: Bool
  , -- | @standardSampleLocations@ specifies whether rasterization uses the
    -- standard sample locations as documented in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-multisampling Multisampling>.
    -- If set to 'Vulkan.Core10.FundamentalTypes.TRUE', the implementation uses
    -- the documented sample locations. If set to
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', the implementation /may/ use
    -- different sample locations.
    PhysicalDeviceLimits -> Bool
standardSampleLocations :: Bool
  , -- | @optimalBufferCopyOffsetAlignment@ is the optimal buffer offset
    -- alignment in bytes for
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage' and
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer'. The per
    -- texel alignment requirements are enforced, but applications /should/ use
    -- the optimal alignment for optimal performance and power use.
    PhysicalDeviceLimits -> DeviceSize
optimalBufferCopyOffsetAlignment :: DeviceSize
  , -- | @optimalBufferCopyRowPitchAlignment@ is the optimal buffer row pitch
    -- alignment in bytes for
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage' and
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer'. Row pitch is
    -- the number of bytes between texels with the same X coordinate in
    -- adjacent rows (Y coordinates differ by one). The per texel alignment
    -- requirements are enforced, but applications /should/ use the optimal
    -- alignment for optimal performance and power use.
    PhysicalDeviceLimits -> DeviceSize
optimalBufferCopyRowPitchAlignment :: DeviceSize
  , -- | @nonCoherentAtomSize@ is the size and alignment in bytes that bounds
    -- concurrent access to
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-device-hostaccess host-mapped device memory>.
    PhysicalDeviceLimits -> DeviceSize
nonCoherentAtomSize :: DeviceSize
  }
  deriving (Typeable, PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool
(PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool)
-> (PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool)
-> Eq PhysicalDeviceLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool
$c/= :: PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool
== :: PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool
$c== :: PhysicalDeviceLimits -> PhysicalDeviceLimits -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceLimits)
#endif
deriving instance Show PhysicalDeviceLimits

instance ToCStruct PhysicalDeviceLimits where
  withCStruct :: PhysicalDeviceLimits -> (Ptr PhysicalDeviceLimits -> IO b) -> IO b
withCStruct x :: PhysicalDeviceLimits
x f :: Ptr PhysicalDeviceLimits -> IO b
f = Int -> Int -> (Ptr PhysicalDeviceLimits -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 504 8 ((Ptr PhysicalDeviceLimits -> IO b) -> IO b)
-> (Ptr PhysicalDeviceLimits -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceLimits
p -> Ptr PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLimits
p PhysicalDeviceLimits
x (Ptr PhysicalDeviceLimits -> IO b
f Ptr PhysicalDeviceLimits
p)
  pokeCStruct :: Ptr PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceLimits
p PhysicalDeviceLimits{..} f :: IO b
f = do
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
maxImageDimension1D)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
maxImageDimension2D)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
maxImageDimension3D)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
maxImageDimensionCube)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
maxImageArrayLayers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
maxTexelBufferElements)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
maxUniformBufferRange)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
maxStorageBufferRange)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
maxPushConstantsSize)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
maxMemoryAllocationCount)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
maxSamplerAllocationCount)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
bufferImageGranularity)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) (DeviceSize
sparseAddressSpaceSize)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
maxBoundDescriptorSets)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
maxPerStageDescriptorSamplers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) (Word32
maxPerStageDescriptorUniformBuffers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) (Word32
maxPerStageDescriptorStorageBuffers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) (Word32
maxPerStageDescriptorSampledImages)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
maxPerStageDescriptorStorageImages)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
maxPerStageDescriptorInputAttachments)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32)) (Word32
maxPerStageResources)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
maxDescriptorSetSamplers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32)) (Word32
maxDescriptorSetUniformBuffers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32)) (Word32
maxDescriptorSetUniformBuffersDynamic)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Word32)) (Word32
maxDescriptorSetStorageBuffers)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Word32)) (Word32
maxDescriptorSetStorageBuffersDynamic)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Word32)) (Word32
maxDescriptorSetSampledImages)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32)) (Word32
maxDescriptorSetStorageImages)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Word32)) (Word32
maxDescriptorSetInputAttachments)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Word32)) (Word32
maxVertexInputAttributes)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Word32)) (Word32
maxVertexInputBindings)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Word32)) (Word32
maxVertexInputAttributeOffset)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Word32)) (Word32
maxVertexInputBindingStride)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Word32)) (Word32
maxVertexOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Word32)) (Word32
maxTessellationGenerationLevel)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Word32)) (Word32
maxTessellationPatchSize)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Word32)) (Word32
maxTessellationControlPerVertexInputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Word32)) (Word32
maxTessellationControlPerVertexOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Word32)) (Word32
maxTessellationControlPerPatchOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Word32)) (Word32
maxTessellationControlTotalOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Word32)) (Word32
maxTessellationEvaluationInputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Word32)) (Word32
maxTessellationEvaluationOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Word32)) (Word32
maxGeometryShaderInvocations)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Word32)) (Word32
maxGeometryInputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Word32)) (Word32
maxGeometryOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Word32)) (Word32
maxGeometryOutputVertices)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Word32)) (Word32
maxGeometryTotalOutputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Word32)) (Word32
maxFragmentInputComponents)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Word32)) (Word32
maxFragmentOutputAttachments)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Word32)) (Word32
maxFragmentDualSrcAttachments)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Word32)) (Word32
maxFragmentCombinedOutputResources)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Word32)) (Word32
maxComputeSharedMemorySize)
    let pMaxComputeWorkGroupCount' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 220 :: Ptr (FixedArray 3 Word32)))
    case ((Word32, Word32, Word32)
maxComputeWorkGroupCount) of
      (e0 :: Word32
e0, e1 :: Word32
e1, e2 :: Word32
e2) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) (Word32
e2)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 232 :: Ptr Word32)) (Word32
maxComputeWorkGroupInvocations)
    let pMaxComputeWorkGroupSize' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 236 :: Ptr (FixedArray 3 Word32)))
    case ((Word32, Word32, Word32)
maxComputeWorkGroupSize) of
      (e0 :: Word32
e0, e1 :: Word32
e1, e2 :: Word32
e2) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) (Word32
e2)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 248 :: Ptr Word32)) (Word32
subPixelPrecisionBits)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 252 :: Ptr Word32)) (Word32
subTexelPrecisionBits)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 256 :: Ptr Word32)) (Word32
mipmapPrecisionBits)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32)) (Word32
maxDrawIndexedIndexValue)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr Word32)) (Word32
maxDrawIndirectCount)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 268 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxSamplerLodBias))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxSamplerAnisotropy))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr Word32)) (Word32
maxViewports)
    let pMaxViewportDimensions' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' = Ptr (FixedArray 2 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 280 :: Ptr (FixedArray 2 Word32)))
    case ((Word32, Word32)
maxViewportDimensions) of
      (e0 :: Word32
e0, e1 :: Word32
e1) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
    let pViewportBoundsRange' :: Ptr CFloat
pViewportBoundsRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 288 :: Ptr (FixedArray 2 CFloat)))
    case ((Float, Float)
viewportBoundsRange) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pViewportBoundsRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pViewportBoundsRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr Word32)) (Word32
viewportSubPixelBits)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 304 :: Ptr CSize)) (DeviceSize -> CSize
CSize (DeviceSize
minMemoryMapAlignment))
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 312 :: Ptr DeviceSize)) (DeviceSize
minTexelBufferOffsetAlignment)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 320 :: Ptr DeviceSize)) (DeviceSize
minUniformBufferOffsetAlignment)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 328 :: Ptr DeviceSize)) (DeviceSize
minStorageBufferOffsetAlignment)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 336 :: Ptr Int32)) (Int32
minTexelOffset)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 340 :: Ptr Word32)) (Word32
maxTexelOffset)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 344 :: Ptr Int32)) (Int32
minTexelGatherOffset)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 348 :: Ptr Word32)) (Word32
maxTexelGatherOffset)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 352 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minInterpolationOffset))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 356 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxInterpolationOffset))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 360 :: Ptr Word32)) (Word32
subPixelInterpolationOffsetBits)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 364 :: Ptr Word32)) (Word32
maxFramebufferWidth)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 368 :: Ptr Word32)) (Word32
maxFramebufferHeight)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 372 :: Ptr Word32)) (Word32
maxFramebufferLayers)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 376 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferColorSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 380 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferDepthSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 384 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferStencilSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 388 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferNoAttachmentsSampleCounts)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 392 :: Ptr Word32)) (Word32
maxColorAttachments)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 396 :: Ptr SampleCountFlags)) (SampleCountFlags
sampledImageColorSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 400 :: Ptr SampleCountFlags)) (SampleCountFlags
sampledImageIntegerSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 404 :: Ptr SampleCountFlags)) (SampleCountFlags
sampledImageDepthSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 408 :: Ptr SampleCountFlags)) (SampleCountFlags
sampledImageStencilSampleCounts)
    Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 412 :: Ptr SampleCountFlags)) (SampleCountFlags
storageImageSampleCounts)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 416 :: Ptr Word32)) (Word32
maxSampleMaskWords)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 420 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
timestampComputeAndGraphics))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 424 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
timestampPeriod))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 428 :: Ptr Word32)) (Word32
maxClipDistances)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 432 :: Ptr Word32)) (Word32
maxCullDistances)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 436 :: Ptr Word32)) (Word32
maxCombinedClipAndCullDistances)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 440 :: Ptr Word32)) (Word32
discreteQueuePriorities)
    let pPointSizeRange' :: Ptr CFloat
pPointSizeRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 444 :: Ptr (FixedArray 2 CFloat)))
    case ((Float, Float)
pointSizeRange) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPointSizeRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPointSizeRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    let pLineWidthRange' :: Ptr CFloat
pLineWidthRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 452 :: Ptr (FixedArray 2 CFloat)))
    case ((Float, Float)
lineWidthRange) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pLineWidthRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pLineWidthRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 460 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
pointSizeGranularity))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 464 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
lineWidthGranularity))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 468 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
strictLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 472 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
standardSampleLocations))
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 480 :: Ptr DeviceSize)) (DeviceSize
optimalBufferCopyOffsetAlignment)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 488 :: Ptr DeviceSize)) (DeviceSize
optimalBufferCopyRowPitchAlignment)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 496 :: Ptr DeviceSize)) (DeviceSize
nonCoherentAtomSize)
    IO b
f
  cStructSize :: Int
cStructSize = 504
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceLimits -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceLimits
p f :: IO b
f = do
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    let pMaxComputeWorkGroupCount' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 220 :: Ptr (FixedArray 3 Word32)))
    case ((Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)) of
      (e0 :: Word32
e0, e1 :: Word32
e1, e2 :: Word32
e2) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupCount' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) (Word32
e2)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 232 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    let pMaxComputeWorkGroupSize' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 236 :: Ptr (FixedArray 3 Word32)))
    case ((Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)) of
      (e0 :: Word32
e0, e1 :: Word32
e1, e2 :: Word32
e2) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxComputeWorkGroupSize' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) (Word32
e2)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 248 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 252 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 256 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 268 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    let pMaxViewportDimensions' :: "pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' = Ptr (FixedArray 2 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 280 :: Ptr (FixedArray 2 Word32)))
    case ((Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)) of
      (e0 :: Word32
e0, e1 :: Word32
e1) -> do
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' :: Ptr Word32) (Word32
e0)
        ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPhysicalDeviceCount" ::: Ptr Word32
pMaxViewportDimensions' ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
    let pViewportBoundsRange' :: Ptr CFloat
pViewportBoundsRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 288 :: Ptr (FixedArray 2 CFloat)))
    case ((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pViewportBoundsRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pViewportBoundsRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 304 :: Ptr CSize)) (DeviceSize -> CSize
CSize (DeviceSize
forall a. Zero a => a
zero))
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 312 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 320 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 328 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 336 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 340 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 344 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 348 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 352 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 356 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 360 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 364 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 368 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 372 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 392 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 416 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 420 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 424 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 428 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 432 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 436 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPhysicalDeviceCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 440 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    let pPointSizeRange' :: Ptr CFloat
pPointSizeRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 444 :: Ptr (FixedArray 2 CFloat)))
    case ((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPointSizeRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPointSizeRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    let pLineWidthRange' :: Ptr CFloat
pLineWidthRange' = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 452 :: Ptr (FixedArray 2 CFloat)))
    case ((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)) of
      (e0 :: Float
e0, e1 :: Float
e1) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pLineWidthRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pLineWidthRange' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 460 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 464 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 468 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 472 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 480 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 488 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 496 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceLimits where
  peekCStruct :: Ptr PhysicalDeviceLimits -> IO PhysicalDeviceLimits
peekCStruct p :: Ptr PhysicalDeviceLimits
p = do
    Word32
maxImageDimension1D <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
maxImageDimension2D <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
maxImageDimension3D <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Word32
maxImageDimensionCube <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    Word32
maxImageArrayLayers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
maxTexelBufferElements <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
maxUniformBufferRange <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Word32
maxStorageBufferRange <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Word32
maxPushConstantsSize <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Word32
maxMemoryAllocationCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32))
    Word32
maxSamplerAllocationCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    DeviceSize
bufferImageGranularity <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize))
    DeviceSize
sparseAddressSpaceSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize))
    Word32
maxBoundDescriptorSets <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    Word32
maxPerStageDescriptorSamplers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32))
    Word32
maxPerStageDescriptorUniformBuffers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32))
    Word32
maxPerStageDescriptorStorageBuffers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32))
    Word32
maxPerStageDescriptorSampledImages <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32))
    Word32
maxPerStageDescriptorStorageImages <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32))
    Word32
maxPerStageDescriptorInputAttachments <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32))
    Word32
maxPerStageResources <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Word32))
    Word32
maxDescriptorSetSamplers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32))
    Word32
maxDescriptorSetUniformBuffers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Word32))
    Word32
maxDescriptorSetUniformBuffersDynamic <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Word32))
    Word32
maxDescriptorSetStorageBuffers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Word32))
    Word32
maxDescriptorSetStorageBuffersDynamic <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Word32))
    Word32
maxDescriptorSetSampledImages <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Word32))
    Word32
maxDescriptorSetStorageImages <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32))
    Word32
maxDescriptorSetInputAttachments <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Word32))
    Word32
maxVertexInputAttributes <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Word32))
    Word32
maxVertexInputBindings <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Word32))
    Word32
maxVertexInputAttributeOffset <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Word32))
    Word32
maxVertexInputBindingStride <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Word32))
    Word32
maxVertexOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Word32))
    Word32
maxTessellationGenerationLevel <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Word32))
    Word32
maxTessellationPatchSize <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Word32))
    Word32
maxTessellationControlPerVertexInputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Word32))
    Word32
maxTessellationControlPerVertexOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Word32))
    Word32
maxTessellationControlPerPatchOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Word32))
    Word32
maxTessellationControlTotalOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Word32))
    Word32
maxTessellationEvaluationInputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Word32))
    Word32
maxTessellationEvaluationOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Word32))
    Word32
maxGeometryShaderInvocations <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Word32))
    Word32
maxGeometryInputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Word32))
    Word32
maxGeometryOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Word32))
    Word32
maxGeometryOutputVertices <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Word32))
    Word32
maxGeometryTotalOutputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Word32))
    Word32
maxFragmentInputComponents <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Word32))
    Word32
maxFragmentOutputAttachments <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 204 :: Ptr Word32))
    Word32
maxFragmentDualSrcAttachments <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 208 :: Ptr Word32))
    Word32
maxFragmentCombinedOutputResources <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 212 :: Ptr Word32))
    Word32
maxComputeSharedMemorySize <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 216 :: Ptr Word32))
    let pmaxComputeWorkGroupCount :: "pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupCount = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 220 :: Ptr (FixedArray 3 Word32)))
    Word32
maxComputeWorkGroupCount0 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupCount ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Word32))
    Word32
maxComputeWorkGroupCount1 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupCount ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr Word32))
    Word32
maxComputeWorkGroupCount2 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupCount ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr Word32))
    Word32
maxComputeWorkGroupInvocations <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 232 :: Ptr Word32))
    let pmaxComputeWorkGroupSize :: "pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupSize = Ptr (FixedArray 3 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 3 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 236 :: Ptr (FixedArray 3 Word32)))
    Word32
maxComputeWorkGroupSize0 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupSize ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Word32))
    Word32
maxComputeWorkGroupSize1 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupSize ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr Word32))
    Word32
maxComputeWorkGroupSize2 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxComputeWorkGroupSize ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr Word32))
    Word32
subPixelPrecisionBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 248 :: Ptr Word32))
    Word32
subTexelPrecisionBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 252 :: Ptr Word32))
    Word32
mipmapPrecisionBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 256 :: Ptr Word32))
    Word32
maxDrawIndexedIndexValue <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 260 :: Ptr Word32))
    Word32
maxDrawIndirectCount <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 264 :: Ptr Word32))
    CFloat
maxSamplerLodBias <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 268 :: Ptr CFloat))
    CFloat
maxSamplerAnisotropy <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 272 :: Ptr CFloat))
    Word32
maxViewports <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr Word32))
    let pmaxViewportDimensions :: "pPhysicalDeviceCount" ::: Ptr Word32
pmaxViewportDimensions = Ptr (FixedArray 2 Word32) -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 280 :: Ptr (FixedArray 2 Word32)))
    Word32
maxViewportDimensions0 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxViewportDimensions ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Word32))
    Word32
maxViewportDimensions1 <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pPhysicalDeviceCount" ::: Ptr Word32
pmaxViewportDimensions ("pPhysicalDeviceCount" ::: Ptr Word32)
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr Word32))
    let pviewportBoundsRange :: Ptr CFloat
pviewportBoundsRange = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 288 :: Ptr (FixedArray 2 CFloat)))
    CFloat
viewportBoundsRange0 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pviewportBoundsRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
viewportBoundsRange1 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pviewportBoundsRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    Word32
viewportSubPixelBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 296 :: Ptr Word32))
    CSize
minMemoryMapAlignment <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 304 :: Ptr CSize))
    DeviceSize
minTexelBufferOffsetAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 312 :: Ptr DeviceSize))
    DeviceSize
minUniformBufferOffsetAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 320 :: Ptr DeviceSize))
    DeviceSize
minStorageBufferOffsetAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 328 :: Ptr DeviceSize))
    Int32
minTexelOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 336 :: Ptr Int32))
    Word32
maxTexelOffset <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 340 :: Ptr Word32))
    Int32
minTexelGatherOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 344 :: Ptr Int32))
    Word32
maxTexelGatherOffset <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 348 :: Ptr Word32))
    CFloat
minInterpolationOffset <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 352 :: Ptr CFloat))
    CFloat
maxInterpolationOffset <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 356 :: Ptr CFloat))
    Word32
subPixelInterpolationOffsetBits <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 360 :: Ptr Word32))
    Word32
maxFramebufferWidth <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 364 :: Ptr Word32))
    Word32
maxFramebufferHeight <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 368 :: Ptr Word32))
    Word32
maxFramebufferLayers <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 372 :: Ptr Word32))
    SampleCountFlags
framebufferColorSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 376 :: Ptr SampleCountFlags))
    SampleCountFlags
framebufferDepthSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 380 :: Ptr SampleCountFlags))
    SampleCountFlags
framebufferStencilSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 384 :: Ptr SampleCountFlags))
    SampleCountFlags
framebufferNoAttachmentsSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 388 :: Ptr SampleCountFlags))
    Word32
maxColorAttachments <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 392 :: Ptr Word32))
    SampleCountFlags
sampledImageColorSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 396 :: Ptr SampleCountFlags))
    SampleCountFlags
sampledImageIntegerSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 400 :: Ptr SampleCountFlags))
    SampleCountFlags
sampledImageDepthSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 404 :: Ptr SampleCountFlags))
    SampleCountFlags
sampledImageStencilSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 408 :: Ptr SampleCountFlags))
    SampleCountFlags
storageImageSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 412 :: Ptr SampleCountFlags))
    Word32
maxSampleMaskWords <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 416 :: Ptr Word32))
    Bool32
timestampComputeAndGraphics <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 420 :: Ptr Bool32))
    CFloat
timestampPeriod <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 424 :: Ptr CFloat))
    Word32
maxClipDistances <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 428 :: Ptr Word32))
    Word32
maxCullDistances <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 432 :: Ptr Word32))
    Word32
maxCombinedClipAndCullDistances <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 436 :: Ptr Word32))
    Word32
discreteQueuePriorities <- ("pPhysicalDeviceCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits
-> Int -> "pPhysicalDeviceCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 440 :: Ptr Word32))
    let ppointSizeRange :: Ptr CFloat
ppointSizeRange = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 444 :: Ptr (FixedArray 2 CFloat)))
    CFloat
pointSizeRange0 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
ppointSizeRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
pointSizeRange1 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
ppointSizeRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    let plineWidthRange :: Ptr CFloat
plineWidthRange = Ptr (FixedArray 2 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr (FixedArray 2 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 452 :: Ptr (FixedArray 2 CFloat)))
    CFloat
lineWidthRange0 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
plineWidthRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
lineWidthRange1 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
plineWidthRange Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    CFloat
pointSizeGranularity <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 460 :: Ptr CFloat))
    CFloat
lineWidthGranularity <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 464 :: Ptr CFloat))
    Bool32
strictLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 468 :: Ptr Bool32))
    Bool32
standardSampleLocations <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 472 :: Ptr Bool32))
    DeviceSize
optimalBufferCopyOffsetAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 480 :: Ptr DeviceSize))
    DeviceSize
optimalBufferCopyRowPitchAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 488 :: Ptr DeviceSize))
    DeviceSize
nonCoherentAtomSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceLimits
p Ptr PhysicalDeviceLimits -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 496 :: Ptr DeviceSize))
    PhysicalDeviceLimits -> IO PhysicalDeviceLimits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceLimits -> IO PhysicalDeviceLimits)
-> PhysicalDeviceLimits -> IO PhysicalDeviceLimits
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> DeviceSize
-> DeviceSize
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> (Word32, Word32, Word32)
-> Word32
-> (Word32, Word32, Word32)
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Float
-> Float
-> Word32
-> (Word32, Word32)
-> (Float, Float)
-> Word32
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> Int32
-> Word32
-> Int32
-> Word32
-> Float
-> Float
-> Word32
-> Word32
-> Word32
-> Word32
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> Word32
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> Word32
-> Bool
-> Float
-> Word32
-> Word32
-> Word32
-> Word32
-> (Float, Float)
-> (Float, Float)
-> Float
-> Float
-> Bool
-> Bool
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> PhysicalDeviceLimits
PhysicalDeviceLimits
             Word32
maxImageDimension1D Word32
maxImageDimension2D Word32
maxImageDimension3D Word32
maxImageDimensionCube Word32
maxImageArrayLayers Word32
maxTexelBufferElements Word32
maxUniformBufferRange Word32
maxStorageBufferRange Word32
maxPushConstantsSize Word32
maxMemoryAllocationCount Word32
maxSamplerAllocationCount DeviceSize
bufferImageGranularity DeviceSize
sparseAddressSpaceSize Word32
maxBoundDescriptorSets Word32
maxPerStageDescriptorSamplers Word32
maxPerStageDescriptorUniformBuffers Word32
maxPerStageDescriptorStorageBuffers Word32
maxPerStageDescriptorSampledImages Word32
maxPerStageDescriptorStorageImages Word32
maxPerStageDescriptorInputAttachments Word32
maxPerStageResources Word32
maxDescriptorSetSamplers Word32
maxDescriptorSetUniformBuffers Word32
maxDescriptorSetUniformBuffersDynamic Word32
maxDescriptorSetStorageBuffers Word32
maxDescriptorSetStorageBuffersDynamic Word32
maxDescriptorSetSampledImages Word32
maxDescriptorSetStorageImages Word32
maxDescriptorSetInputAttachments Word32
maxVertexInputAttributes Word32
maxVertexInputBindings Word32
maxVertexInputAttributeOffset Word32
maxVertexInputBindingStride Word32
maxVertexOutputComponents Word32
maxTessellationGenerationLevel Word32
maxTessellationPatchSize Word32
maxTessellationControlPerVertexInputComponents Word32
maxTessellationControlPerVertexOutputComponents Word32
maxTessellationControlPerPatchOutputComponents Word32
maxTessellationControlTotalOutputComponents Word32
maxTessellationEvaluationInputComponents Word32
maxTessellationEvaluationOutputComponents Word32
maxGeometryShaderInvocations Word32
maxGeometryInputComponents Word32
maxGeometryOutputComponents Word32
maxGeometryOutputVertices Word32
maxGeometryTotalOutputComponents Word32
maxFragmentInputComponents Word32
maxFragmentOutputAttachments Word32
maxFragmentDualSrcAttachments Word32
maxFragmentCombinedOutputResources Word32
maxComputeSharedMemorySize ((Word32
maxComputeWorkGroupCount0, Word32
maxComputeWorkGroupCount1, Word32
maxComputeWorkGroupCount2)) Word32
maxComputeWorkGroupInvocations ((Word32
maxComputeWorkGroupSize0, Word32
maxComputeWorkGroupSize1, Word32
maxComputeWorkGroupSize2)) Word32
subPixelPrecisionBits Word32
subTexelPrecisionBits Word32
mipmapPrecisionBits Word32
maxDrawIndexedIndexValue Word32
maxDrawIndirectCount ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxSamplerLodBias) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxSamplerAnisotropy) Word32
maxViewports ((Word32
maxViewportDimensions0, Word32
maxViewportDimensions1)) ((((\(CFloat a :: Float
a) -> Float
a) CFloat
viewportBoundsRange0), ((\(CFloat a :: Float
a) -> Float
a) CFloat
viewportBoundsRange1))) Word32
viewportSubPixelBits ((\(CSize a :: DeviceSize
a) -> DeviceSize
a) CSize
minMemoryMapAlignment) DeviceSize
minTexelBufferOffsetAlignment DeviceSize
minUniformBufferOffsetAlignment DeviceSize
minStorageBufferOffsetAlignment Int32
minTexelOffset Word32
maxTexelOffset Int32
minTexelGatherOffset Word32
maxTexelGatherOffset ((\(CFloat a :: Float
a) -> Float
a) CFloat
minInterpolationOffset) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxInterpolationOffset) Word32
subPixelInterpolationOffsetBits Word32
maxFramebufferWidth Word32
maxFramebufferHeight Word32
maxFramebufferLayers SampleCountFlags
framebufferColorSampleCounts SampleCountFlags
framebufferDepthSampleCounts SampleCountFlags
framebufferStencilSampleCounts SampleCountFlags
framebufferNoAttachmentsSampleCounts Word32
maxColorAttachments SampleCountFlags
sampledImageColorSampleCounts SampleCountFlags
sampledImageIntegerSampleCounts SampleCountFlags
sampledImageDepthSampleCounts SampleCountFlags
sampledImageStencilSampleCounts SampleCountFlags
storageImageSampleCounts Word32
maxSampleMaskWords (Bool32 -> Bool
bool32ToBool Bool32
timestampComputeAndGraphics) ((\(CFloat a :: Float
a) -> Float
a) CFloat
timestampPeriod) Word32
maxClipDistances Word32
maxCullDistances Word32
maxCombinedClipAndCullDistances Word32
discreteQueuePriorities ((((\(CFloat a :: Float
a) -> Float
a) CFloat
pointSizeRange0), ((\(CFloat a :: Float
a) -> Float
a) CFloat
pointSizeRange1))) ((((\(CFloat a :: Float
a) -> Float
a) CFloat
lineWidthRange0), ((\(CFloat a :: Float
a) -> Float
a) CFloat
lineWidthRange1))) ((\(CFloat a :: Float
a) -> Float
a) CFloat
pointSizeGranularity) ((\(CFloat a :: Float
a) -> Float
a) CFloat
lineWidthGranularity) (Bool32 -> Bool
bool32ToBool Bool32
strictLines) (Bool32 -> Bool
bool32ToBool Bool32
standardSampleLocations) DeviceSize
optimalBufferCopyOffsetAlignment DeviceSize
optimalBufferCopyRowPitchAlignment DeviceSize
nonCoherentAtomSize

instance Storable PhysicalDeviceLimits where
  sizeOf :: PhysicalDeviceLimits -> Int
sizeOf ~PhysicalDeviceLimits
_ = 504
  alignment :: PhysicalDeviceLimits -> Int
alignment ~PhysicalDeviceLimits
_ = 8
  peek :: Ptr PhysicalDeviceLimits -> IO PhysicalDeviceLimits
peek = Ptr PhysicalDeviceLimits -> IO PhysicalDeviceLimits
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO ()
poke ptr :: Ptr PhysicalDeviceLimits
ptr poked :: PhysicalDeviceLimits
poked = Ptr PhysicalDeviceLimits -> PhysicalDeviceLimits -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLimits
ptr PhysicalDeviceLimits
poked (FN_vkVoidFunction
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceLimits where
  zero :: PhysicalDeviceLimits
zero = Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> DeviceSize
-> DeviceSize
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> (Word32, Word32, Word32)
-> Word32
-> (Word32, Word32, Word32)
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Float
-> Float
-> Word32
-> (Word32, Word32)
-> (Float, Float)
-> Word32
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> Int32
-> Word32
-> Int32
-> Word32
-> Float
-> Float
-> Word32
-> Word32
-> Word32
-> Word32
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> Word32
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> SampleCountFlags
-> Word32
-> Bool
-> Float
-> Word32
-> Word32
-> Word32
-> Word32
-> (Float, Float)
-> (Float, Float)
-> Float
-> Float
-> Bool
-> Bool
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> PhysicalDeviceLimits
PhysicalDeviceLimits
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           (Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)
           Word32
forall a. Zero a => a
zero
           (Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           (Word32
forall a. Zero a => a
zero, Word32
forall a. Zero a => a
zero)
           (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)
           Word32
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)
           (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero