{-# language CPP #-}
-- | = Name
--
-- VK_AMD_shader_core_properties2 - device extension
--
-- == VK_AMD_shader_core_properties2
--
-- [__Name String__]
--     @VK_AMD_shader_core_properties2@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     228
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_AMD_shader_core_properties@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Matthaeus G. Chajdas
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_AMD_shader_core_properties2] @anteru%0A*Here describe the issue or question you have about the VK_AMD_shader_core_properties2 extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-07-26
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Matthaeus G. Chajdas, AMD
--
--     -   Tobias Hector, AMD
--
-- == Description
--
-- This extension exposes additional shader core properties for a target
-- physical device through the @VK_KHR_get_physical_device_properties2@
-- extension.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceShaderCoreProperties2AMD'
--
-- == New Enums
--
-- -   'ShaderCorePropertiesFlagBitsAMD'
--
-- == New Bitmasks
--
-- -   'ShaderCorePropertiesFlagsAMD'
--
-- == New Enum Constants
--
-- -   'AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME'
--
-- -   'AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD'
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2019-07-26 (Matthaeus G. Chajdas)
--
--     -   Initial draft.
--
-- == See Also
--
-- 'PhysicalDeviceShaderCoreProperties2AMD',
-- 'ShaderCorePropertiesFlagBitsAMD', 'ShaderCorePropertiesFlagsAMD'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_AMD_shader_core_properties2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_AMD_shader_core_properties2  ( PhysicalDeviceShaderCoreProperties2AMD(..)
                                                         , ShaderCorePropertiesFlagsAMD
                                                         , ShaderCorePropertiesFlagBitsAMD(..)
                                                         , AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION
                                                         , pattern AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION
                                                         , AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME
                                                         , pattern AMD_SHADER_CORE_PROPERTIES_2_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 (Flags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD))
-- | VkPhysicalDeviceShaderCoreProperties2AMD - Structure describing shader
-- core properties that can be supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceShaderCoreProperties2AMD' 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_AMD_shader_core_properties2 VK_AMD_shader_core_properties2>,
-- 'ShaderCorePropertiesFlagsAMD',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceShaderCoreProperties2AMD = PhysicalDeviceShaderCoreProperties2AMD
  { -- | #features-shaderCoreFeatures# @shaderCoreFeatures@ is a bitmask of
    -- 'ShaderCorePropertiesFlagBitsAMD' indicating the set of features
    -- supported by the shader core.
    PhysicalDeviceShaderCoreProperties2AMD
-> ShaderCorePropertiesFlagBitsAMD
shaderCoreFeatures :: ShaderCorePropertiesFlagsAMD
  , -- | #limits-activeComputeUnitCount# @activeComputeUnitCount@ is an unsigned
    -- integer value indicating the number of compute units that have been
    -- enabled.
    PhysicalDeviceShaderCoreProperties2AMD -> Word32
activeComputeUnitCount :: Word32
  }
  deriving (Typeable, PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> Bool
$c/= :: PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> Bool
== :: PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> Bool
$c== :: PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderCoreProperties2AMD)
#endif
deriving instance Show PhysicalDeviceShaderCoreProperties2AMD

instance ToCStruct PhysicalDeviceShaderCoreProperties2AMD where
  withCStruct :: forall b.
PhysicalDeviceShaderCoreProperties2AMD
-> (Ptr PhysicalDeviceShaderCoreProperties2AMD -> IO b) -> IO b
withCStruct PhysicalDeviceShaderCoreProperties2AMD
x Ptr PhysicalDeviceShaderCoreProperties2AMD -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceShaderCoreProperties2AMD
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderCoreProperties2AMD
p PhysicalDeviceShaderCoreProperties2AMD
x (Ptr PhysicalDeviceShaderCoreProperties2AMD -> IO b
f Ptr PhysicalDeviceShaderCoreProperties2AMD
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceShaderCoreProperties2AMD
-> PhysicalDeviceShaderCoreProperties2AMD -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderCoreProperties2AMD
p PhysicalDeviceShaderCoreProperties2AMD{Word32
ShaderCorePropertiesFlagBitsAMD
activeComputeUnitCount :: Word32
shaderCoreFeatures :: ShaderCorePropertiesFlagBitsAMD
$sel:activeComputeUnitCount:PhysicalDeviceShaderCoreProperties2AMD :: PhysicalDeviceShaderCoreProperties2AMD -> Word32
$sel:shaderCoreFeatures:PhysicalDeviceShaderCoreProperties2AMD :: PhysicalDeviceShaderCoreProperties2AMD
-> ShaderCorePropertiesFlagBitsAMD
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
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 PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ShaderCorePropertiesFlagsAMD)) (ShaderCorePropertiesFlagBitsAMD
shaderCoreFeatures)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Word32
activeComputeUnitCount)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceShaderCoreProperties2AMD -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceShaderCoreProperties2AMD
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
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 PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ShaderCorePropertiesFlagsAMD)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCoreProperties2AMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

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

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

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


type ShaderCorePropertiesFlagsAMD = ShaderCorePropertiesFlagBitsAMD

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

conNameShaderCorePropertiesFlagBitsAMD :: String
conNameShaderCorePropertiesFlagBitsAMD :: String
conNameShaderCorePropertiesFlagBitsAMD = String
"ShaderCorePropertiesFlagBitsAMD"

enumPrefixShaderCorePropertiesFlagBitsAMD :: String
enumPrefixShaderCorePropertiesFlagBitsAMD :: String
enumPrefixShaderCorePropertiesFlagBitsAMD = String
""

showTableShaderCorePropertiesFlagBitsAMD :: [(ShaderCorePropertiesFlagBitsAMD, String)]
showTableShaderCorePropertiesFlagBitsAMD :: [(ShaderCorePropertiesFlagBitsAMD, String)]
showTableShaderCorePropertiesFlagBitsAMD = []

instance Show ShaderCorePropertiesFlagBitsAMD where
  showsPrec :: Int -> ShaderCorePropertiesFlagBitsAMD -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixShaderCorePropertiesFlagBitsAMD
      [(ShaderCorePropertiesFlagBitsAMD, String)]
showTableShaderCorePropertiesFlagBitsAMD
      String
conNameShaderCorePropertiesFlagBitsAMD
      (\(ShaderCorePropertiesFlagBitsAMD Word32
x) -> Word32
x)
      (\Word32
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
x)

instance Read ShaderCorePropertiesFlagBitsAMD where
  readPrec :: ReadPrec ShaderCorePropertiesFlagBitsAMD
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixShaderCorePropertiesFlagBitsAMD
      [(ShaderCorePropertiesFlagBitsAMD, String)]
showTableShaderCorePropertiesFlagBitsAMD
      String
conNameShaderCorePropertiesFlagBitsAMD
      Word32 -> ShaderCorePropertiesFlagBitsAMD
ShaderCorePropertiesFlagBitsAMD

type AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION"
pattern AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bAMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION :: forall a. Integral a => a
$mAMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_SHADER_CORE_PROPERTIES_2_SPEC_VERSION = 1


type AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME = "VK_AMD_shader_core_properties2"

-- No documentation found for TopLevel "VK_AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME"
pattern AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bAMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mAMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_SHADER_CORE_PROPERTIES_2_EXTENSION_NAME = "VK_AMD_shader_core_properties2"