{-# language CPP #-}
-- | = Name
--
-- VK_ARM_scheduling_controls - device extension
--
-- == VK_ARM_scheduling_controls
--
-- [__Name String__]
--     @VK_ARM_scheduling_controls@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     418
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ARM_shader_core_builtins VK_ARM_shader_core_builtins>
--
-- [__Contact__]
--
--     -   Kevin Petit
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_ARM_scheduling_controls] @kpet%0A*Here describe the issue or question you have about the VK_ARM_scheduling_controls extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-08-23
--
-- [__Interactions and External Dependencies__]
--     None
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Kévin Petit, Arm Ltd.
--
--     -   Jan-Harald Fredriksen, Arm Ltd.
--
--     -   Mikel Garai, Arm Ltd.
--
-- == Description
--
-- This extension exposes a collection of controls to modify the scheduling
-- behaviour of Arm Mali devices.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.Device.DeviceQueueCreateInfo',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'DeviceQueueShaderCoreControlCreateInfoARM'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceSchedulingControlsFeaturesARM'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceSchedulingControlsPropertiesARM'
--
-- == New Enums
--
-- -   'PhysicalDeviceSchedulingControlsFlagBitsARM'
--
-- == New Bitmasks
--
-- -   'PhysicalDeviceSchedulingControlsFlagsARM'
--
-- == New Enum Constants
--
-- -   'ARM_SCHEDULING_CONTROLS_EXTENSION_NAME'
--
-- -   'ARM_SCHEDULING_CONTROLS_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_QUEUE_SHADER_CORE_CONTROL_CREATE_INFO_ARM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_FEATURES_ARM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_PROPERTIES_ARM'
--
-- == New SPIR-V Capabilities
--
-- None.
--
-- == Issues
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2023-08-23 (Kévin Petit)
--
--     -   Initial revision
--
-- == See Also
--
-- 'DeviceQueueShaderCoreControlCreateInfoARM',
-- 'PhysicalDeviceSchedulingControlsFeaturesARM',
-- 'PhysicalDeviceSchedulingControlsFlagBitsARM',
-- 'PhysicalDeviceSchedulingControlsFlagsARM',
-- 'PhysicalDeviceSchedulingControlsPropertiesARM'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_ARM_scheduling_controls Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_ARM_scheduling_controls  ( DeviceQueueShaderCoreControlCreateInfoARM(..)
                                                     , PhysicalDeviceSchedulingControlsFeaturesARM(..)
                                                     , PhysicalDeviceSchedulingControlsPropertiesARM(..)
                                                     , PhysicalDeviceSchedulingControlsFlagsARM
                                                     , PhysicalDeviceSchedulingControlsFlagBitsARM( PHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM
                                                                                                  , ..
                                                                                                  )
                                                     , ARM_SCHEDULING_CONTROLS_SPEC_VERSION
                                                     , pattern ARM_SCHEDULING_CONTROLS_SPEC_VERSION
                                                     , ARM_SCHEDULING_CONTROLS_EXTENSION_NAME
                                                     , pattern ARM_SCHEDULING_CONTROLS_EXTENSION_NAME
                                                     ) where

import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import 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 Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Flags64)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_QUEUE_SHADER_CORE_CONTROL_CREATE_INFO_ARM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_FEATURES_ARM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_PROPERTIES_ARM))
-- | VkDeviceQueueShaderCoreControlCreateInfoARM - Control the number of
-- shader cores used by queues
--
-- = Description
--
-- Queues created without specifying
-- 'DeviceQueueShaderCoreControlCreateInfoARM' will default to using all
-- the shader cores available.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ARM_scheduling_controls VK_ARM_scheduling_controls>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceQueueShaderCoreControlCreateInfoARM = DeviceQueueShaderCoreControlCreateInfoARM
  { -- | @shaderCoreCount@ is the number of shader cores this queue uses.
    --
    -- #VUID-VkDeviceQueueShaderCoreControlCreateInfoARM-shaderCoreCount-09399#
    -- @shaderCoreCount@ /must/ be greater than 0 and less than or equal to the
    -- total number of shader cores as reported via
    -- 'Vulkan.Extensions.VK_ARM_shader_core_builtins.PhysicalDeviceShaderCoreBuiltinsPropertiesARM'::@shaderCoreCount@.
    DeviceQueueShaderCoreControlCreateInfoARM -> Word32
shaderCoreCount :: Word32 }
  deriving (Typeable, DeviceQueueShaderCoreControlCreateInfoARM
-> DeviceQueueShaderCoreControlCreateInfoARM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceQueueShaderCoreControlCreateInfoARM
-> DeviceQueueShaderCoreControlCreateInfoARM -> Bool
$c/= :: DeviceQueueShaderCoreControlCreateInfoARM
-> DeviceQueueShaderCoreControlCreateInfoARM -> Bool
== :: DeviceQueueShaderCoreControlCreateInfoARM
-> DeviceQueueShaderCoreControlCreateInfoARM -> Bool
$c== :: DeviceQueueShaderCoreControlCreateInfoARM
-> DeviceQueueShaderCoreControlCreateInfoARM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceQueueShaderCoreControlCreateInfoARM)
#endif
deriving instance Show DeviceQueueShaderCoreControlCreateInfoARM

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

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

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

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


-- | VkPhysicalDeviceSchedulingControlsFeaturesARM - Structure describing
-- scheduling controls features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceSchedulingControlsFeaturesARM' 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. 'PhysicalDeviceSchedulingControlsFeaturesARM' /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_ARM_scheduling_controls VK_ARM_scheduling_controls>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceSchedulingControlsFeaturesARM = PhysicalDeviceSchedulingControlsFeaturesARM
  { -- | #features-schedulingControls# @schedulingControls@ indicates that the
    -- implementation supports scheduling controls.
    PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
schedulingControls :: Bool }
  deriving (Typeable, PhysicalDeviceSchedulingControlsFeaturesARM
-> PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSchedulingControlsFeaturesARM
-> PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
$c/= :: PhysicalDeviceSchedulingControlsFeaturesARM
-> PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
== :: PhysicalDeviceSchedulingControlsFeaturesARM
-> PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
$c== :: PhysicalDeviceSchedulingControlsFeaturesARM
-> PhysicalDeviceSchedulingControlsFeaturesARM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSchedulingControlsFeaturesARM)
#endif
deriving instance Show PhysicalDeviceSchedulingControlsFeaturesARM

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

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

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

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


-- | VkPhysicalDeviceSchedulingControlsPropertiesARM - Structure containing
-- scheduling control properties of a physical device
--
-- = Members
--
-- -   #limits-schedulingControlsFlags#@schedulingControlsFlags@ specifies
--     the specific scheduling controls that a physical device supports.
--
-- = Description
--
-- If the 'PhysicalDeviceSchedulingControlsPropertiesARM' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ARM_scheduling_controls VK_ARM_scheduling_controls>,
-- 'PhysicalDeviceSchedulingControlsFlagsARM',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceSchedulingControlsPropertiesARM = PhysicalDeviceSchedulingControlsPropertiesARM
  { -- | #VUID-VkPhysicalDeviceSchedulingControlsPropertiesARM-schedulingControlsFlags-parameter#
    -- @schedulingControlsFlags@ /must/ be a valid combination of
    -- 'PhysicalDeviceSchedulingControlsFlagBitsARM' values
    --
    -- #VUID-VkPhysicalDeviceSchedulingControlsPropertiesARM-schedulingControlsFlags-requiredbitmask#
    -- @schedulingControlsFlags@ /must/ not be @0@
    PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
schedulingControlsFlags :: PhysicalDeviceSchedulingControlsFlagsARM }
  deriving (Typeable, PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> Bool
$c/= :: PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> Bool
== :: PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> Bool
$c== :: PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSchedulingControlsPropertiesARM)
#endif
deriving instance Show PhysicalDeviceSchedulingControlsPropertiesARM

instance ToCStruct PhysicalDeviceSchedulingControlsPropertiesARM where
  withCStruct :: forall b.
PhysicalDeviceSchedulingControlsPropertiesARM
-> (Ptr PhysicalDeviceSchedulingControlsPropertiesARM -> IO b)
-> IO b
withCStruct PhysicalDeviceSchedulingControlsPropertiesARM
x Ptr PhysicalDeviceSchedulingControlsPropertiesARM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p PhysicalDeviceSchedulingControlsPropertiesARM
x (Ptr PhysicalDeviceSchedulingControlsPropertiesARM -> IO b
f Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsPropertiesARM -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p PhysicalDeviceSchedulingControlsPropertiesARM{PhysicalDeviceSchedulingControlsFlagBitsARM
schedulingControlsFlags :: PhysicalDeviceSchedulingControlsFlagBitsARM
$sel:schedulingControlsFlags:PhysicalDeviceSchedulingControlsPropertiesARM :: PhysicalDeviceSchedulingControlsPropertiesARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_PROPERTIES_ARM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PhysicalDeviceSchedulingControlsFlagsARM)) (PhysicalDeviceSchedulingControlsFlagBitsARM
schedulingControlsFlags)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceSchedulingControlsPropertiesARM -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SCHEDULING_CONTROLS_PROPERTIES_ARM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PhysicalDeviceSchedulingControlsFlagsARM)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceSchedulingControlsPropertiesARM where
  peekCStruct :: Ptr PhysicalDeviceSchedulingControlsPropertiesARM
-> IO PhysicalDeviceSchedulingControlsPropertiesARM
peekCStruct Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p = do
    PhysicalDeviceSchedulingControlsFlagBitsARM
schedulingControlsFlags <- forall a. Storable a => Ptr a -> IO a
peek @PhysicalDeviceSchedulingControlsFlagsARM ((Ptr PhysicalDeviceSchedulingControlsPropertiesARM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PhysicalDeviceSchedulingControlsFlagsARM))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsPropertiesARM
PhysicalDeviceSchedulingControlsPropertiesARM
             PhysicalDeviceSchedulingControlsFlagBitsARM
schedulingControlsFlags

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

instance Zero PhysicalDeviceSchedulingControlsPropertiesARM where
  zero :: PhysicalDeviceSchedulingControlsPropertiesARM
zero = PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsPropertiesARM
PhysicalDeviceSchedulingControlsPropertiesARM
           forall a. Zero a => a
zero


type PhysicalDeviceSchedulingControlsFlagsARM = PhysicalDeviceSchedulingControlsFlagBitsARM

-- | VkPhysicalDeviceSchedulingControlsFlagBitsARM - Bitmask specifying
-- scheduling controls supported by a physical device
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ARM_scheduling_controls VK_ARM_scheduling_controls>
newtype PhysicalDeviceSchedulingControlsFlagBitsARM = PhysicalDeviceSchedulingControlsFlagBitsARM Flags64
  deriving newtype (PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c/= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
== :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c== :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
Eq, Eq PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Ordering
PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$cmin :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
max :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$cmax :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
>= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c>= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
> :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c> :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
<= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c<= :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
< :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$c< :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
compare :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Ordering
$ccompare :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> Ordering
Ord, Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> IO PhysicalDeviceSchedulingControlsFlagBitsARM
Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
forall b.
Ptr b -> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
forall b.
Ptr b
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
$cpoke :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
peek :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> IO PhysicalDeviceSchedulingControlsFlagBitsARM
$cpeek :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> IO PhysicalDeviceSchedulingControlsFlagBitsARM
pokeByteOff :: forall b.
Ptr b
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
peekByteOff :: forall b.
Ptr b -> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
$cpeekByteOff :: forall b.
Ptr b -> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
pokeElemOff :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
$cpokeElemOff :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> IO ()
peekElemOff :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
$cpeekElemOff :: Ptr PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> IO PhysicalDeviceSchedulingControlsFlagBitsARM
alignment :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$calignment :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
sizeOf :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$csizeOf :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
Storable, PhysicalDeviceSchedulingControlsFlagBitsARM
forall a. a -> Zero a
zero :: PhysicalDeviceSchedulingControlsFlagBitsARM
$czero :: PhysicalDeviceSchedulingControlsFlagBitsARM
Zero, Eq PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM
Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
PhysicalDeviceSchedulingControlsFlagBitsARM -> Maybe Int
PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM -> Int -> Bool
PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$cpopCount :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
rotateR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$crotateR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
rotateL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$crotateL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
unsafeShiftR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cunsafeShiftR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
shiftR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cshiftR :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
unsafeShiftL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cunsafeShiftL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
shiftL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cshiftL :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
isSigned :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
$cisSigned :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Bool
bitSize :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$cbitSize :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
bitSizeMaybe :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Maybe Int
$cbitSizeMaybe :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Maybe Int
testBit :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int -> Bool
$ctestBit :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int -> Bool
complementBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$ccomplementBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
clearBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cclearBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
setBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$csetBit :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
bit :: Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cbit :: Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
zeroBits :: PhysicalDeviceSchedulingControlsFlagBitsARM
$czeroBits :: PhysicalDeviceSchedulingControlsFlagBitsARM
rotate :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$crotate :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
shift :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
$cshift :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> Int -> PhysicalDeviceSchedulingControlsFlagBitsARM
complement :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$ccomplement :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
xor :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$cxor :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
.|. :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$c.|. :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
.&. :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
$c.&. :: PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
-> PhysicalDeviceSchedulingControlsFlagBitsARM
Bits, Bits PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$ccountTrailingZeros :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
countLeadingZeros :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$ccountLeadingZeros :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
finiteBitSize :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
$cfiniteBitSize :: PhysicalDeviceSchedulingControlsFlagBitsARM -> Int
FiniteBits)

-- | 'PHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM' indicates
-- that a 'DeviceQueueShaderCoreControlCreateInfoARM' structure /may/ be
-- included in the @pNext@ chain of a
-- 'Vulkan.Core10.Device.DeviceQueueCreateInfo' or
-- 'Vulkan.Core10.Device.DeviceCreateInfo' structure.
pattern $bPHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM :: PhysicalDeviceSchedulingControlsFlagBitsARM
$mPHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM :: forall {r}.
PhysicalDeviceSchedulingControlsFlagBitsARM
-> ((# #) -> r) -> ((# #) -> r) -> r
PHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM = PhysicalDeviceSchedulingControlsFlagBitsARM 0x0000000000000001

conNamePhysicalDeviceSchedulingControlsFlagBitsARM :: String
conNamePhysicalDeviceSchedulingControlsFlagBitsARM :: String
conNamePhysicalDeviceSchedulingControlsFlagBitsARM = String
"PhysicalDeviceSchedulingControlsFlagBitsARM"

enumPrefixPhysicalDeviceSchedulingControlsFlagBitsARM :: String
enumPrefixPhysicalDeviceSchedulingControlsFlagBitsARM :: String
enumPrefixPhysicalDeviceSchedulingControlsFlagBitsARM = String
"PHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM"

showTablePhysicalDeviceSchedulingControlsFlagBitsARM :: [(PhysicalDeviceSchedulingControlsFlagBitsARM, String)]
showTablePhysicalDeviceSchedulingControlsFlagBitsARM :: [(PhysicalDeviceSchedulingControlsFlagBitsARM, String)]
showTablePhysicalDeviceSchedulingControlsFlagBitsARM =
  [
    ( PhysicalDeviceSchedulingControlsFlagBitsARM
PHYSICAL_DEVICE_SCHEDULING_CONTROLS_SHADER_CORE_COUNT_ARM
    , String
""
    )
  ]

instance Show PhysicalDeviceSchedulingControlsFlagBitsARM where
  showsPrec :: Int -> PhysicalDeviceSchedulingControlsFlagBitsARM -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPhysicalDeviceSchedulingControlsFlagBitsARM
      [(PhysicalDeviceSchedulingControlsFlagBitsARM, String)]
showTablePhysicalDeviceSchedulingControlsFlagBitsARM
      String
conNamePhysicalDeviceSchedulingControlsFlagBitsARM
      (\(PhysicalDeviceSchedulingControlsFlagBitsARM Flags64
x) -> Flags64
x)
      (\Flags64
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags64
x)

instance Read PhysicalDeviceSchedulingControlsFlagBitsARM where
  readPrec :: ReadPrec PhysicalDeviceSchedulingControlsFlagBitsARM
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPhysicalDeviceSchedulingControlsFlagBitsARM
      [(PhysicalDeviceSchedulingControlsFlagBitsARM, String)]
showTablePhysicalDeviceSchedulingControlsFlagBitsARM
      String
conNamePhysicalDeviceSchedulingControlsFlagBitsARM
      Flags64 -> PhysicalDeviceSchedulingControlsFlagBitsARM
PhysicalDeviceSchedulingControlsFlagBitsARM

type ARM_SCHEDULING_CONTROLS_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_ARM_SCHEDULING_CONTROLS_SPEC_VERSION"
pattern ARM_SCHEDULING_CONTROLS_SPEC_VERSION :: forall a . Integral a => a
pattern $bARM_SCHEDULING_CONTROLS_SPEC_VERSION :: forall a. Integral a => a
$mARM_SCHEDULING_CONTROLS_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ARM_SCHEDULING_CONTROLS_SPEC_VERSION = 1


type ARM_SCHEDULING_CONTROLS_EXTENSION_NAME = "VK_ARM_scheduling_controls"

-- No documentation found for TopLevel "VK_ARM_SCHEDULING_CONTROLS_EXTENSION_NAME"
pattern ARM_SCHEDULING_CONTROLS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bARM_SCHEDULING_CONTROLS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mARM_SCHEDULING_CONTROLS_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ARM_SCHEDULING_CONTROLS_EXTENSION_NAME = "VK_ARM_scheduling_controls"