{-# language CPP #-}
-- | = Name
--
-- VK_EXT_global_priority_query - device extension
--
-- == VK_EXT_global_priority_query
--
-- [__Name String__]
--     @VK_EXT_global_priority_query@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     389
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_EXT_global_priority@
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Contact__]
--
--     -   Yiwei Zhang
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_global_priority_query] @zhangyiwei%0A<<Here describe the issue or question you have about the VK_EXT_global_priority_query extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2021-03-29
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Yiwei Zhang, Google
--
-- == Description
--
-- This device extension allows applications to query the global queue
-- priorities supported by a queue family. It allows implementations to
-- report which global priority levels are treated differently by the
-- implementation, instead of silently mapping multiple requested global
-- priority levels to the same internal priority, or using device creation
-- failure to signal that a requested priority is not supported. It is
-- intended primarily for use by system integration along with certain
-- platform-specific priority enforcement rules.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceGlobalPriorityQueryFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.QueueFamilyProperties2':
--
--     -   'QueueFamilyGlobalPriorityPropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME'
--
-- -   'EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION'
--
-- -   'Vulkan.Core10.APIConstants.MAX_GLOBAL_PRIORITY_SIZE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_GLOBAL_PRIORITY_QUERY_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUEUE_FAMILY_GLOBAL_PRIORITY_PROPERTIES_EXT'
--
-- == Issues
--
-- 1) Can we additionally query whether a caller is permitted to acquire a
-- specific global queue priority in this extension?
--
-- __RESOLVED__: No. Whether a caller has enough privilege goes with the
-- OS, and the Vulkan driver cannot really guarantee that the privilege
-- will not change in between this query and the actual queue creation
-- call.
--
-- 2) If more than 1 queue using global priority is requested, is there a
-- good way to know which queue is failing the device creation?
--
-- __RESOLVED__: No. There is not a good way at this moment, and it is also
-- not quite actionable for the applications to know that because the
-- information may not be accurate. Queue creation can fail because of
-- runtime constraints like insufficient privilege or lack of resource, and
-- the failure is not necessarily tied to that particular queue
-- configuration requested.
--
-- == Version History
--
-- -   Revision 1, 2021-03-29 (Yiwei Zhang)
--
-- = See Also
--
-- 'Vulkan.Core10.APIConstants.MAX_GLOBAL_PRIORITY_SIZE_EXT',
-- 'PhysicalDeviceGlobalPriorityQueryFeaturesEXT',
-- 'QueueFamilyGlobalPriorityPropertiesEXT'
--
-- = Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_global_priority_query Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_global_priority_query  ( PhysicalDeviceGlobalPriorityQueryFeaturesEXT(..)
                                                       , QueueFamilyGlobalPriorityPropertiesEXT(..)
                                                       , EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION
                                                       , pattern EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION
                                                       , EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME
                                                       , pattern EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME
                                                       , QueueGlobalPriorityEXT(..)
                                                       , MAX_GLOBAL_PRIORITY_SIZE_EXT
                                                       , pattern MAX_GLOBAL_PRIORITY_SIZE_EXT
                                                       ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Monad (unless)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
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 (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.APIConstants (MAX_GLOBAL_PRIORITY_SIZE_EXT)
import Vulkan.Extensions.VK_EXT_global_priority (QueueGlobalPriorityEXT)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.APIConstants (pattern MAX_GLOBAL_PRIORITY_SIZE_EXT)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_GLOBAL_PRIORITY_QUERY_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUEUE_FAMILY_GLOBAL_PRIORITY_PROPERTIES_EXT))
import Vulkan.Core10.APIConstants (MAX_GLOBAL_PRIORITY_SIZE_EXT)
import Vulkan.Extensions.VK_EXT_global_priority (QueueGlobalPriorityEXT(..))
import Vulkan.Core10.APIConstants (pattern MAX_GLOBAL_PRIORITY_SIZE_EXT)
-- | VkPhysicalDeviceGlobalPriorityQueryFeaturesEXT - Structure describing
-- whether global priority query can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceGlobalPriorityQueryFeaturesEXT'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceGlobalPriorityQueryFeaturesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceGlobalPriorityQueryFeaturesEXT' /can/ also be
-- used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_global_priority_query VK_EXT_global_priority_query>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceGlobalPriorityQueryFeaturesEXT = PhysicalDeviceGlobalPriorityQueryFeaturesEXT
  { -- | #features-globalPriorityQuery# @globalPriorityQuery@ indicates whether
    -- the implementation supports the ability to query global queue
    -- priorities.
    PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
globalPriorityQuery :: Bool }
  deriving (Typeable, PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
(PhysicalDeviceGlobalPriorityQueryFeaturesEXT
 -> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool)
-> (PhysicalDeviceGlobalPriorityQueryFeaturesEXT
    -> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool)
-> Eq PhysicalDeviceGlobalPriorityQueryFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
$c/= :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
== :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
$c== :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceGlobalPriorityQueryFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceGlobalPriorityQueryFeaturesEXT

instance ToCStruct PhysicalDeviceGlobalPriorityQueryFeaturesEXT where
  withCStruct :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> (Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceGlobalPriorityQueryFeaturesEXT
x Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p -> Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p PhysicalDeviceGlobalPriorityQueryFeaturesEXT
x (Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b
f Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p PhysicalDeviceGlobalPriorityQueryFeaturesEXT{Bool
globalPriorityQuery :: Bool
$sel:globalPriorityQuery:PhysicalDeviceGlobalPriorityQueryFeaturesEXT :: PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_GLOBAL_PRIORITY_QUERY_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
globalPriorityQuery))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_GLOBAL_PRIORITY_QUERY_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceGlobalPriorityQueryFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> IO PhysicalDeviceGlobalPriorityQueryFeaturesEXT
peekCStruct Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p = do
    Bool32
globalPriorityQuery <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
p Ptr PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> IO PhysicalDeviceGlobalPriorityQueryFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceGlobalPriorityQueryFeaturesEXT
 -> IO PhysicalDeviceGlobalPriorityQueryFeaturesEXT)
-> PhysicalDeviceGlobalPriorityQueryFeaturesEXT
-> IO PhysicalDeviceGlobalPriorityQueryFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceGlobalPriorityQueryFeaturesEXT
PhysicalDeviceGlobalPriorityQueryFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
globalPriorityQuery)

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

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


-- | VkQueueFamilyGlobalPriorityPropertiesEXT - Return structure for queue
-- family global priority information query
--
-- = Description
--
-- The valid elements of @priorities@ /must/ not contain any duplicate
-- values.
--
-- The valid elements of @priorities@ /must/ be a continuous sequence of
-- 'Vulkan.Extensions.VK_EXT_global_priority.QueueGlobalPriorityEXT' enums
-- in the ascending order.
--
-- Note
--
-- For example, returning @priorityCount@ as 3 with supported @priorities@
-- as
-- 'Vulkan.Extensions.VK_EXT_global_priority.QUEUE_GLOBAL_PRIORITY_LOW_EXT',
-- 'Vulkan.Extensions.VK_EXT_global_priority.QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT'
-- and
-- 'Vulkan.Extensions.VK_EXT_global_priority.QUEUE_GLOBAL_PRIORITY_REALTIME_EXT'
-- is not allowed.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkQueueFamilyGlobalPriorityPropertiesEXT-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUEUE_FAMILY_GLOBAL_PRIORITY_PROPERTIES_EXT'
--
-- -   #VUID-VkQueueFamilyGlobalPriorityPropertiesEXT-priorities-parameter#
--     Any given element of @priorities@ /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_global_priority.QueueGlobalPriorityEXT'
--     value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_global_priority_query VK_EXT_global_priority_query>,
-- 'Vulkan.Extensions.VK_EXT_global_priority.QueueGlobalPriorityEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data QueueFamilyGlobalPriorityPropertiesEXT = QueueFamilyGlobalPriorityPropertiesEXT
  { -- | @priorityCount@ is the number of supported global queue priorities in
    -- this queue family, and it /must/ be greater than 0.
    QueueFamilyGlobalPriorityPropertiesEXT -> Word32
priorityCount :: Word32
  , -- | @priorities@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_GLOBAL_PRIORITY_SIZE_EXT'
    -- 'Vulkan.Extensions.VK_EXT_global_priority.QueueGlobalPriorityEXT' enums
    -- representing all supported global queue priorities in this queue family.
    -- The first @priorityCount@ elements of the array will be valid.
    QueueFamilyGlobalPriorityPropertiesEXT
-> Vector QueueGlobalPriorityEXT
priorities :: Vector QueueGlobalPriorityEXT
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueueFamilyGlobalPriorityPropertiesEXT)
#endif
deriving instance Show QueueFamilyGlobalPriorityPropertiesEXT

instance ToCStruct QueueFamilyGlobalPriorityPropertiesEXT where
  withCStruct :: QueueFamilyGlobalPriorityPropertiesEXT
-> (Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b) -> IO b
withCStruct QueueFamilyGlobalPriorityPropertiesEXT
x Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b
f = Int -> (Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
88 ((Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b) -> IO b)
-> (Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr QueueFamilyGlobalPriorityPropertiesEXT
p -> Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> QueueFamilyGlobalPriorityPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr QueueFamilyGlobalPriorityPropertiesEXT
p QueueFamilyGlobalPriorityPropertiesEXT
x (Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b
f Ptr QueueFamilyGlobalPriorityPropertiesEXT
p)
  pokeCStruct :: Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> QueueFamilyGlobalPriorityPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr QueueFamilyGlobalPriorityPropertiesEXT
p QueueFamilyGlobalPriorityPropertiesEXT{Word32
Vector QueueGlobalPriorityEXT
priorities :: Vector QueueGlobalPriorityEXT
priorityCount :: Word32
$sel:priorities:QueueFamilyGlobalPriorityPropertiesEXT :: QueueFamilyGlobalPriorityPropertiesEXT
-> Vector QueueGlobalPriorityEXT
$sel:priorityCount:QueueFamilyGlobalPriorityPropertiesEXT :: QueueFamilyGlobalPriorityPropertiesEXT -> Word32
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUEUE_FAMILY_GLOBAL_PRIORITY_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
priorityCount)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector QueueGlobalPriorityEXT -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector QueueGlobalPriorityEXT -> Int)
-> Vector QueueGlobalPriorityEXT -> Int
forall a b. (a -> b) -> a -> b
$ (Vector QueueGlobalPriorityEXT
priorities)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_GLOBAL_PRIORITY_SIZE_EXT) (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 String
"" String
"priorities is too long, a maximum of MAX_GLOBAL_PRIORITY_SIZE_EXT elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> QueueGlobalPriorityEXT -> IO ())
-> Vector QueueGlobalPriorityEXT -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i QueueGlobalPriorityEXT
e -> Ptr QueueGlobalPriorityEXT -> QueueGlobalPriorityEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr
  (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)
-> Ptr QueueGlobalPriorityEXT
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> Int
-> Ptr
     (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)))) Ptr QueueGlobalPriorityEXT -> Int -> Ptr QueueGlobalPriorityEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr QueueGlobalPriorityEXT) (QueueGlobalPriorityEXT
e)) (Vector QueueGlobalPriorityEXT
priorities)
    IO b
f
  cStructSize :: Int
cStructSize = Int
88
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr QueueFamilyGlobalPriorityPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr QueueFamilyGlobalPriorityPropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUEUE_FAMILY_GLOBAL_PRIORITY_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct QueueFamilyGlobalPriorityPropertiesEXT where
  peekCStruct :: Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> IO QueueFamilyGlobalPriorityPropertiesEXT
peekCStruct Ptr QueueFamilyGlobalPriorityPropertiesEXT
p = do
    Word32
priorityCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Vector QueueGlobalPriorityEXT
priorities <- Int
-> (Int -> IO QueueGlobalPriorityEXT)
-> IO (Vector QueueGlobalPriorityEXT)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_GLOBAL_PRIORITY_SIZE_EXT) (\Int
i -> Ptr QueueGlobalPriorityEXT -> IO QueueGlobalPriorityEXT
forall a. Storable a => Ptr a -> IO a
peek @QueueGlobalPriorityEXT (((Ptr
  (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)
-> Ptr QueueGlobalPriorityEXT
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @QueueGlobalPriorityEXT ((Ptr QueueFamilyGlobalPriorityPropertiesEXT
p Ptr QueueFamilyGlobalPriorityPropertiesEXT
-> Int
-> Ptr
     (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr (FixedArray MAX_GLOBAL_PRIORITY_SIZE_EXT QueueGlobalPriorityEXT)))) Ptr QueueGlobalPriorityEXT -> Int -> Ptr QueueGlobalPriorityEXT
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr QueueGlobalPriorityEXT)))
    QueueFamilyGlobalPriorityPropertiesEXT
-> IO QueueFamilyGlobalPriorityPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueueFamilyGlobalPriorityPropertiesEXT
 -> IO QueueFamilyGlobalPriorityPropertiesEXT)
-> QueueFamilyGlobalPriorityPropertiesEXT
-> IO QueueFamilyGlobalPriorityPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32
-> Vector QueueGlobalPriorityEXT
-> QueueFamilyGlobalPriorityPropertiesEXT
QueueFamilyGlobalPriorityPropertiesEXT
             Word32
priorityCount Vector QueueGlobalPriorityEXT
priorities

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

instance Zero QueueFamilyGlobalPriorityPropertiesEXT where
  zero :: QueueFamilyGlobalPriorityPropertiesEXT
zero = Word32
-> Vector QueueGlobalPriorityEXT
-> QueueFamilyGlobalPriorityPropertiesEXT
QueueFamilyGlobalPriorityPropertiesEXT
           Word32
forall a. Zero a => a
zero
           Vector QueueGlobalPriorityEXT
forall a. Monoid a => a
mempty


type EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION"
pattern EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION :: a
$mEXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_GLOBAL_PRIORITY_QUERY_SPEC_VERSION = 1


type EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME = "VK_EXT_global_priority_query"

-- No documentation found for TopLevel "VK_EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME"
pattern EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME :: a
$mEXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_GLOBAL_PRIORITY_QUERY_EXTENSION_NAME = "VK_EXT_global_priority_query"