{-# language CPP #-}
module Vulkan.Extensions.VK_AMD_shader_core_properties  ( PhysicalDeviceShaderCorePropertiesAMD(..)
                                                        , AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION
                                                        , pattern AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION
                                                        , AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME
                                                        , pattern AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME
                                                        ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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 Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_AMD))
-- | VkPhysicalDeviceShaderCorePropertiesAMD - Structure describing shader
-- core properties that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceShaderCorePropertiesAMD' structure
-- describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceShaderCorePropertiesAMD' structure is included in
-- the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceShaderCorePropertiesAMD = PhysicalDeviceShaderCorePropertiesAMD
  { -- | @shaderEngineCount@ is an unsigned integer value indicating the number
    -- of shader engines found inside the shader core of the physical device.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
shaderEngineCount :: Word32
  , -- | @shaderArraysPerEngineCount@ is an unsigned integer value indicating the
    -- number of shader arrays inside a shader engine. Each shader array has
    -- its own scan converter, set of compute units, and a render back end
    -- (color and depth buffers). Shader arrays within a shader engine share
    -- shader processor input (wave launcher) and shader export (export buffer)
    -- units. Currently, a shader engine can have one or two shader arrays.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
shaderArraysPerEngineCount :: Word32
  , -- | @computeUnitsPerShaderArray@ is an unsigned integer value indicating the
    -- physical number of compute units within a shader array. The active
    -- number of compute units in a shader array /may/ be lower. A compute unit
    -- houses a set of SIMDs along with a sequencer module and a local data
    -- store.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
computeUnitsPerShaderArray :: Word32
  , -- | @simdPerComputeUnit@ is an unsigned integer value indicating the number
    -- of SIMDs inside a compute unit. Each SIMD processes a single instruction
    -- at a time.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
simdPerComputeUnit :: Word32
  , -- No documentation found for Nested "VkPhysicalDeviceShaderCorePropertiesAMD" "wavefrontsPerSimd"
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
wavefrontsPerSimd :: Word32
  , -- | @wavefrontSize@ is an unsigned integer value indicating the maximum size
    -- of a subgroup.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
wavefrontSize :: Word32
  , -- | @sgprsPerSimd@ is an unsigned integer value indicating the number of
    -- physical Scalar General Purpose Registers (SGPRs) per SIMD.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
sgprsPerSimd :: Word32
  , -- | @minSgprAllocation@ is an unsigned integer value indicating the minimum
    -- number of SGPRs allocated for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
minSgprAllocation :: Word32
  , -- | @maxSgprAllocation@ is an unsigned integer value indicating the maximum
    -- number of SGPRs allocated for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
maxSgprAllocation :: Word32
  , -- | @sgprAllocationGranularity@ is an unsigned integer value indicating the
    -- granularity of SGPR allocation for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
sgprAllocationGranularity :: Word32
  , -- | @vgprsPerSimd@ is an unsigned integer value indicating the number of
    -- physical Vector General Purpose Registers (VGPRs) per SIMD.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
vgprsPerSimd :: Word32
  , -- | @minVgprAllocation@ is an unsigned integer value indicating the minimum
    -- number of VGPRs allocated for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
minVgprAllocation :: Word32
  , -- | @maxVgprAllocation@ is an unsigned integer value indicating the maximum
    -- number of VGPRs allocated for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
maxVgprAllocation :: Word32
  , -- | @vgprAllocationGranularity@ is an unsigned integer value indicating the
    -- granularity of VGPR allocation for a wave.
    PhysicalDeviceShaderCorePropertiesAMD -> Word32
vgprAllocationGranularity :: Word32
  }
  deriving (Typeable, PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> Bool
(PhysicalDeviceShaderCorePropertiesAMD
 -> PhysicalDeviceShaderCorePropertiesAMD -> Bool)
-> (PhysicalDeviceShaderCorePropertiesAMD
    -> PhysicalDeviceShaderCorePropertiesAMD -> Bool)
-> Eq PhysicalDeviceShaderCorePropertiesAMD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> Bool
$c/= :: PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> Bool
== :: PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> Bool
$c== :: PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderCorePropertiesAMD)
#endif
deriving instance Show PhysicalDeviceShaderCorePropertiesAMD

instance ToCStruct PhysicalDeviceShaderCorePropertiesAMD where
  withCStruct :: PhysicalDeviceShaderCorePropertiesAMD
-> (Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b) -> IO b
withCStruct x :: PhysicalDeviceShaderCorePropertiesAMD
x f :: Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b) -> IO b)
-> (Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceShaderCorePropertiesAMD
p -> Ptr PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderCorePropertiesAMD
p PhysicalDeviceShaderCorePropertiesAMD
x (Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b
f Ptr PhysicalDeviceShaderCorePropertiesAMD
p)
  pokeCStruct :: Ptr PhysicalDeviceShaderCorePropertiesAMD
-> PhysicalDeviceShaderCorePropertiesAMD -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceShaderCorePropertiesAMD
p PhysicalDeviceShaderCorePropertiesAMD{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
shaderEngineCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
shaderArraysPerEngineCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
computeUnitsPerShaderArray)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
simdPerComputeUnit)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
wavefrontsPerSimd)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
wavefrontSize)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
sgprsPerSimd)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
minSgprAllocation)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
maxSgprAllocation)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
sgprAllocationGranularity)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
vgprsPerSimd)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) (Word32
minVgprAllocation)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
maxVgprAllocation)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
vgprAllocationGranularity)
    IO b
f
  cStructSize :: Int
cStructSize = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceShaderCorePropertiesAMD -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceShaderCorePropertiesAMD
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceShaderCorePropertiesAMD where
  peekCStruct :: Ptr PhysicalDeviceShaderCorePropertiesAMD
-> IO PhysicalDeviceShaderCorePropertiesAMD
peekCStruct p :: Ptr PhysicalDeviceShaderCorePropertiesAMD
p = do
    Word32
shaderEngineCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
shaderArraysPerEngineCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
computeUnitsPerShaderArray <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Word32
simdPerComputeUnit <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Word32
wavefrontsPerSimd <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Word32
wavefrontSize <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32))
    Word32
sgprsPerSimd <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    Word32
minSgprAllocation <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32))
    Word32
maxSgprAllocation <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Word32
sgprAllocationGranularity <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32))
    Word32
vgprsPerSimd <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    Word32
minVgprAllocation <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32))
    Word32
maxVgprAllocation <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    Word32
vgprAllocationGranularity <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderCorePropertiesAMD
p Ptr PhysicalDeviceShaderCorePropertiesAMD -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32))
    PhysicalDeviceShaderCorePropertiesAMD
-> IO PhysicalDeviceShaderCorePropertiesAMD
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceShaderCorePropertiesAMD
 -> IO PhysicalDeviceShaderCorePropertiesAMD)
-> PhysicalDeviceShaderCorePropertiesAMD
-> IO PhysicalDeviceShaderCorePropertiesAMD
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> PhysicalDeviceShaderCorePropertiesAMD
PhysicalDeviceShaderCorePropertiesAMD
             Word32
shaderEngineCount Word32
shaderArraysPerEngineCount Word32
computeUnitsPerShaderArray Word32
simdPerComputeUnit Word32
wavefrontsPerSimd Word32
wavefrontSize Word32
sgprsPerSimd Word32
minSgprAllocation Word32
maxSgprAllocation Word32
sgprAllocationGranularity Word32
vgprsPerSimd Word32
minVgprAllocation Word32
maxVgprAllocation Word32
vgprAllocationGranularity

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

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


type AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION"
pattern AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION :: forall a . Integral a => a
pattern $bAMD_SHADER_CORE_PROPERTIES_SPEC_VERSION :: a
$mAMD_SHADER_CORE_PROPERTIES_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
AMD_SHADER_CORE_PROPERTIES_SPEC_VERSION = 2


type AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME = "VK_AMD_shader_core_properties"

-- No documentation found for TopLevel "VK_AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME"
pattern AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bAMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME :: a
$mAMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
AMD_SHADER_CORE_PROPERTIES_EXTENSION_NAME = "VK_AMD_shader_core_properties"