{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_maintenance3  ( getDescriptorSetLayoutSupport
                                                        , PhysicalDeviceMaintenance3Properties(..)
                                                        , DescriptorSetLayoutSupport(..)
                                                        , StructureType(..)
                                                        ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
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 Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.DescriptorSet (DescriptorSetLayoutCreateInfo)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing (DescriptorSetVariableDescriptorCountLayoutSupport)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetDescriptorSetLayoutSupport))
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MAINTENANCE_3_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDescriptorSetLayoutSupport
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct DescriptorSetLayoutCreateInfo) -> Ptr (SomeStruct DescriptorSetLayoutSupport) -> IO ()) -> Ptr Device_T -> Ptr (SomeStruct DescriptorSetLayoutCreateInfo) -> Ptr (SomeStruct DescriptorSetLayoutSupport) -> IO ()

-- | vkGetDescriptorSetLayoutSupport - Query whether a descriptor set layout
-- can be created
--
-- = Description
--
-- Some implementations have limitations on what fits in a descriptor set
-- which are not easily expressible in terms of existing limits like
-- @maxDescriptorSet@*, for example if all descriptor types share a limited
-- space in memory but each descriptor is a different size or alignment.
-- This command returns information about whether a descriptor set
-- satisfies this limit. If the descriptor set layout satisfies the
-- 'PhysicalDeviceMaintenance3Properties'::@maxPerSetDescriptors@ limit,
-- this command is guaranteed to return
-- 'Vulkan.Core10.FundamentalTypes.TRUE' in
-- 'DescriptorSetLayoutSupport'::@supported@. If the descriptor set layout
-- exceeds the
-- 'PhysicalDeviceMaintenance3Properties'::@maxPerSetDescriptors@ limit,
-- whether the descriptor set layout is supported is
-- implementation-dependent and /may/ depend on whether the descriptor
-- sizes and alignments cause the layout to exceed an internal limit.
--
-- This command does not consider other limits such as
-- @maxPerStageDescriptor@*, and so a descriptor set layout that is
-- supported according to this command /must/ still satisfy the pipeline
-- layout limits such as @maxPerStageDescriptor@* in order to be used in a
-- pipeline layout.
--
-- Note
--
-- This is a 'Vulkan.Core10.Handles.Device' query rather than
-- 'Vulkan.Core10.Handles.PhysicalDevice' because the answer /may/ depend
-- on enabled features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo',
-- 'DescriptorSetLayoutSupport', 'Vulkan.Core10.Handles.Device'
getDescriptorSetLayoutSupport :: forall a b io
                               . (Extendss DescriptorSetLayoutCreateInfo a, Extendss DescriptorSetLayoutSupport b, PokeChain a, PokeChain b, PeekChain b, MonadIO io)
                              => -- | @device@ is the logical device that would create the descriptor set
                                 -- layout.
                                 --
                                 -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                 Device
                              -> -- | @pCreateInfo@ is a pointer to a
                                 -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo' structure
                                 -- specifying the state of the descriptor set layout object.
                                 --
                                 -- @pCreateInfo@ /must/ be a valid pointer to a valid
                                 -- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutCreateInfo' structure
                                 (DescriptorSetLayoutCreateInfo a)
                              -> io (DescriptorSetLayoutSupport b)
getDescriptorSetLayoutSupport :: Device
-> DescriptorSetLayoutCreateInfo a
-> io (DescriptorSetLayoutSupport b)
getDescriptorSetLayoutSupport device :: Device
device createInfo :: DescriptorSetLayoutCreateInfo a
createInfo = IO (DescriptorSetLayoutSupport b)
-> io (DescriptorSetLayoutSupport b)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DescriptorSetLayoutSupport b)
 -> io (DescriptorSetLayoutSupport b))
-> (ContT
      (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
    -> IO (DescriptorSetLayoutSupport b))
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
-> io (DescriptorSetLayoutSupport b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
-> IO (DescriptorSetLayoutSupport b)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
 -> io (DescriptorSetLayoutSupport b))
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
-> io (DescriptorSetLayoutSupport b)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDescriptorSetLayoutSupportPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> IO ())
vkGetDescriptorSetLayoutSupportPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo"
          ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
      -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
      -> IO ())
pVkGetDescriptorSetLayoutSupport (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (DescriptorSetLayoutSupport b) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (DescriptorSetLayoutSupport b) IO ())
-> IO () -> ContT (DescriptorSetLayoutSupport b) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> IO ())
vkGetDescriptorSetLayoutSupportPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo"
          ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
      -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> 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 vkGetDescriptorSetLayoutSupport is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDescriptorSetLayoutSupport' :: Ptr Device_T
-> ("pCreateInfo"
    ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
-> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
-> IO ()
vkGetDescriptorSetLayoutSupport' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> IO ())
-> Ptr Device_T
-> ("pCreateInfo"
    ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
-> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
-> IO ()
mkVkGetDescriptorSetLayoutSupport FunPtr
  (Ptr Device_T
   -> ("pCreateInfo"
       ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
   -> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
   -> IO ())
vkGetDescriptorSetLayoutSupportPtr
  Ptr (DescriptorSetLayoutCreateInfo a)
pCreateInfo <- ((Ptr (DescriptorSetLayoutCreateInfo a)
  -> IO (DescriptorSetLayoutSupport b))
 -> IO (DescriptorSetLayoutSupport b))
-> ContT
     (DescriptorSetLayoutSupport b)
     IO
     (Ptr (DescriptorSetLayoutCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (DescriptorSetLayoutCreateInfo a)
   -> IO (DescriptorSetLayoutSupport b))
  -> IO (DescriptorSetLayoutSupport b))
 -> ContT
      (DescriptorSetLayoutSupport b)
      IO
      (Ptr (DescriptorSetLayoutCreateInfo a)))
-> ((Ptr (DescriptorSetLayoutCreateInfo a)
     -> IO (DescriptorSetLayoutSupport b))
    -> IO (DescriptorSetLayoutSupport b))
-> ContT
     (DescriptorSetLayoutSupport b)
     IO
     (Ptr (DescriptorSetLayoutCreateInfo a))
forall a b. (a -> b) -> a -> b
$ DescriptorSetLayoutCreateInfo a
-> (Ptr (DescriptorSetLayoutCreateInfo a)
    -> IO (DescriptorSetLayoutSupport b))
-> IO (DescriptorSetLayoutSupport b)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DescriptorSetLayoutCreateInfo a
createInfo)
  Ptr (DescriptorSetLayoutSupport b)
pPSupport <- ((Ptr (DescriptorSetLayoutSupport b)
  -> IO (DescriptorSetLayoutSupport b))
 -> IO (DescriptorSetLayoutSupport b))
-> ContT
     (DescriptorSetLayoutSupport b)
     IO
     (Ptr (DescriptorSetLayoutSupport b))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (DescriptorSetLayoutSupport b) =>
(Ptr (DescriptorSetLayoutSupport b) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(DescriptorSetLayoutSupport _))
  IO () -> ContT (DescriptorSetLayoutSupport b) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (DescriptorSetLayoutSupport b) IO ())
-> IO () -> ContT (DescriptorSetLayoutSupport b) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo"
    ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo))
-> ("pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport))
-> IO ()
vkGetDescriptorSetLayoutSupport' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (DescriptorSetLayoutCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct DescriptorSetLayoutCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (DescriptorSetLayoutCreateInfo a)
pCreateInfo) (Ptr (DescriptorSetLayoutSupport b)
-> "pSupport" ::: Ptr (SomeStruct DescriptorSetLayoutSupport)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (DescriptorSetLayoutSupport b)
pPSupport))
  DescriptorSetLayoutSupport b
pSupport <- IO (DescriptorSetLayoutSupport b)
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (DescriptorSetLayoutSupport b)
 -> ContT
      (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b))
-> IO (DescriptorSetLayoutSupport b)
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
forall a b. (a -> b) -> a -> b
$ Ptr (DescriptorSetLayoutSupport b)
-> IO (DescriptorSetLayoutSupport b)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(DescriptorSetLayoutSupport _) Ptr (DescriptorSetLayoutSupport b)
pPSupport
  DescriptorSetLayoutSupport b
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DescriptorSetLayoutSupport b
 -> ContT
      (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b))
-> DescriptorSetLayoutSupport b
-> ContT
     (DescriptorSetLayoutSupport b) IO (DescriptorSetLayoutSupport b)
forall a b. (a -> b) -> a -> b
$ (DescriptorSetLayoutSupport b
pSupport)


-- | VkPhysicalDeviceMaintenance3Properties - Structure describing descriptor
-- set properties
--
-- = Members
--
-- The members of the 'PhysicalDeviceMaintenance3Properties' structure
-- describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceMaintenance3Properties' structure is included in
-- the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceMaintenance3Properties = PhysicalDeviceMaintenance3Properties
  { -- | @maxPerSetDescriptors@ is a maximum number of descriptors (summed over
    -- all descriptor types) in a single descriptor set that is guaranteed to
    -- satisfy any implementation-dependent constraints on the size of a
    -- descriptor set itself. Applications /can/ query whether a descriptor set
    -- that goes beyond this limit is supported using
    -- 'getDescriptorSetLayoutSupport'.
    PhysicalDeviceMaintenance3Properties -> Word32
maxPerSetDescriptors :: Word32
  , -- | @maxMemoryAllocationSize@ is the maximum size of a memory allocation
    -- that /can/ be created, even if there is more space available in the
    -- heap.
    PhysicalDeviceMaintenance3Properties -> DeviceSize
maxMemoryAllocationSize :: DeviceSize
  }
  deriving (Typeable, PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> Bool
(PhysicalDeviceMaintenance3Properties
 -> PhysicalDeviceMaintenance3Properties -> Bool)
-> (PhysicalDeviceMaintenance3Properties
    -> PhysicalDeviceMaintenance3Properties -> Bool)
-> Eq PhysicalDeviceMaintenance3Properties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> Bool
$c/= :: PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> Bool
== :: PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> Bool
$c== :: PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMaintenance3Properties)
#endif
deriving instance Show PhysicalDeviceMaintenance3Properties

instance ToCStruct PhysicalDeviceMaintenance3Properties where
  withCStruct :: PhysicalDeviceMaintenance3Properties
-> (Ptr PhysicalDeviceMaintenance3Properties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMaintenance3Properties
x f :: Ptr PhysicalDeviceMaintenance3Properties -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceMaintenance3Properties -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PhysicalDeviceMaintenance3Properties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceMaintenance3Properties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMaintenance3Properties
p -> Ptr PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMaintenance3Properties
p PhysicalDeviceMaintenance3Properties
x (Ptr PhysicalDeviceMaintenance3Properties -> IO b
f Ptr PhysicalDeviceMaintenance3Properties
p)
  pokeCStruct :: Ptr PhysicalDeviceMaintenance3Properties
-> PhysicalDeviceMaintenance3Properties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceMaintenance3Properties
p PhysicalDeviceMaintenance3Properties{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MAINTENANCE_3_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
maxPerSetDescriptors)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
maxMemoryAllocationSize)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMaintenance3Properties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMaintenance3Properties
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MAINTENANCE_3_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceMaintenance3Properties where
  peekCStruct :: Ptr PhysicalDeviceMaintenance3Properties
-> IO PhysicalDeviceMaintenance3Properties
peekCStruct p :: Ptr PhysicalDeviceMaintenance3Properties
p = do
    Word32
maxPerSetDescriptors <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    DeviceSize
maxMemoryAllocationSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceMaintenance3Properties
p Ptr PhysicalDeviceMaintenance3Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
    PhysicalDeviceMaintenance3Properties
-> IO PhysicalDeviceMaintenance3Properties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMaintenance3Properties
 -> IO PhysicalDeviceMaintenance3Properties)
-> PhysicalDeviceMaintenance3Properties
-> IO PhysicalDeviceMaintenance3Properties
forall a b. (a -> b) -> a -> b
$ Word32 -> DeviceSize -> PhysicalDeviceMaintenance3Properties
PhysicalDeviceMaintenance3Properties
             Word32
maxPerSetDescriptors DeviceSize
maxMemoryAllocationSize

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

instance Zero PhysicalDeviceMaintenance3Properties where
  zero :: PhysicalDeviceMaintenance3Properties
zero = Word32 -> DeviceSize -> PhysicalDeviceMaintenance3Properties
PhysicalDeviceMaintenance3Properties
           Word32
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


-- | VkDescriptorSetLayoutSupport - Structure returning information about
-- whether a descriptor set layout can be supported
--
-- = Description
--
-- @supported@ is set to 'Vulkan.Core10.FundamentalTypes.TRUE' if the
-- descriptor set /can/ be created, or else is set to
-- 'Vulkan.Core10.FundamentalTypes.FALSE'.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.DescriptorSetVariableDescriptorCountLayoutSupport'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getDescriptorSetLayoutSupport',
-- 'Vulkan.Extensions.VK_KHR_maintenance3.getDescriptorSetLayoutSupportKHR'
data DescriptorSetLayoutSupport (es :: [Type]) = DescriptorSetLayoutSupport
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    DescriptorSetLayoutSupport es -> Chain es
next :: Chain es
  , -- | @supported@ specifies whether the descriptor set layout /can/ be
    -- created.
    DescriptorSetLayoutSupport es -> Bool
supported :: Bool
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DescriptorSetLayoutSupport (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (DescriptorSetLayoutSupport es)

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

instance (Extendss DescriptorSetLayoutSupport es, PokeChain es) => ToCStruct (DescriptorSetLayoutSupport es) where
  withCStruct :: DescriptorSetLayoutSupport es
-> (Ptr (DescriptorSetLayoutSupport es) -> IO b) -> IO b
withCStruct x :: DescriptorSetLayoutSupport es
x f :: Ptr (DescriptorSetLayoutSupport es) -> IO b
f = Int -> Int -> (Ptr (DescriptorSetLayoutSupport es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr (DescriptorSetLayoutSupport es) -> IO b) -> IO b)
-> (Ptr (DescriptorSetLayoutSupport es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (DescriptorSetLayoutSupport es)
p -> Ptr (DescriptorSetLayoutSupport es)
-> DescriptorSetLayoutSupport es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (DescriptorSetLayoutSupport es)
p DescriptorSetLayoutSupport es
x (Ptr (DescriptorSetLayoutSupport es) -> IO b
f Ptr (DescriptorSetLayoutSupport es)
p)
  pokeCStruct :: Ptr (DescriptorSetLayoutSupport es)
-> DescriptorSetLayoutSupport es -> IO b -> IO b
pokeCStruct p :: Ptr (DescriptorSetLayoutSupport es)
p DescriptorSetLayoutSupport{..} 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 (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT)
    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 (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport 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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
supported))
    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 = 8
  pokeZeroCStruct :: Ptr (DescriptorSetLayoutSupport es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (DescriptorSetLayoutSupport 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 (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT)
    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 (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport 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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport es) -> 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 -> 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 DescriptorSetLayoutSupport es, PeekChain es) => FromCStruct (DescriptorSetLayoutSupport es) where
  peekCStruct :: Ptr (DescriptorSetLayoutSupport es)
-> IO (DescriptorSetLayoutSupport es)
peekCStruct p :: Ptr (DescriptorSetLayoutSupport es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport 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)
    Bool32
supported <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (DescriptorSetLayoutSupport es)
p Ptr (DescriptorSetLayoutSupport es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    DescriptorSetLayoutSupport es -> IO (DescriptorSetLayoutSupport es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DescriptorSetLayoutSupport es
 -> IO (DescriptorSetLayoutSupport es))
-> DescriptorSetLayoutSupport es
-> IO (DescriptorSetLayoutSupport es)
forall a b. (a -> b) -> a -> b
$ Chain es -> Bool -> DescriptorSetLayoutSupport es
forall (es :: [*]).
Chain es -> Bool -> DescriptorSetLayoutSupport es
DescriptorSetLayoutSupport
             Chain es
next (Bool32 -> Bool
bool32ToBool Bool32
supported)

instance es ~ '[] => Zero (DescriptorSetLayoutSupport es) where
  zero :: DescriptorSetLayoutSupport es
zero = Chain es -> Bool -> DescriptorSetLayoutSupport es
forall (es :: [*]).
Chain es -> Bool -> DescriptorSetLayoutSupport es
DescriptorSetLayoutSupport
           ()
           Bool
forall a. Zero a => a
zero