{-# language CPP #-}
module Vulkan.Extensions.VK_NV_shader_sm_builtins ( PhysicalDeviceShaderSMBuiltinsPropertiesNV(..)
, PhysicalDeviceShaderSMBuiltinsFeaturesNV(..)
, NV_SHADER_SM_BUILTINS_SPEC_VERSION
, pattern NV_SHADER_SM_BUILTINS_SPEC_VERSION
, NV_SHADER_SM_BUILTINS_EXTENSION_NAME
, pattern NV_SHADER_SM_BUILTINS_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
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.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_PROPERTIES_NV))
data PhysicalDeviceShaderSMBuiltinsPropertiesNV = PhysicalDeviceShaderSMBuiltinsPropertiesNV
{
PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Word32
shaderSMCount :: Word32
,
PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Word32
shaderWarpsPerSM :: Word32
}
deriving (Typeable, PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Bool
$c/= :: PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Bool
== :: PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Bool
$c== :: PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderSMBuiltinsPropertiesNV)
#endif
deriving instance Show PhysicalDeviceShaderSMBuiltinsPropertiesNV
instance ToCStruct PhysicalDeviceShaderSMBuiltinsPropertiesNV where
withCStruct :: forall b.
PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> (Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO b) -> IO b
withCStruct PhysicalDeviceShaderSMBuiltinsPropertiesNV
x Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p PhysicalDeviceShaderSMBuiltinsPropertiesNV
x (Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO b
f Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p PhysicalDeviceShaderSMBuiltinsPropertiesNV{Word32
shaderWarpsPerSM :: Word32
shaderSMCount :: Word32
$sel:shaderWarpsPerSM:PhysicalDeviceShaderSMBuiltinsPropertiesNV :: PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Word32
$sel:shaderSMCount:PhysicalDeviceShaderSMBuiltinsPropertiesNV :: PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
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 PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
shaderSMCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Word32
shaderWarpsPerSM)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
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 PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
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 PhysicalDeviceShaderSMBuiltinsPropertiesNV where
peekCStruct :: Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> IO PhysicalDeviceShaderSMBuiltinsPropertiesNV
peekCStruct Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p = do
Word32
shaderSMCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Word32
shaderWarpsPerSM <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
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
$ Word32 -> Word32 -> PhysicalDeviceShaderSMBuiltinsPropertiesNV
PhysicalDeviceShaderSMBuiltinsPropertiesNV
Word32
shaderSMCount Word32
shaderWarpsPerSM
instance Storable PhysicalDeviceShaderSMBuiltinsPropertiesNV where
sizeOf :: PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Int
sizeOf ~PhysicalDeviceShaderSMBuiltinsPropertiesNV
_ = Int
24
alignment :: PhysicalDeviceShaderSMBuiltinsPropertiesNV -> Int
alignment ~PhysicalDeviceShaderSMBuiltinsPropertiesNV
_ = Int
8
peek :: Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> IO PhysicalDeviceShaderSMBuiltinsPropertiesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
-> PhysicalDeviceShaderSMBuiltinsPropertiesNV -> IO ()
poke Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
ptr PhysicalDeviceShaderSMBuiltinsPropertiesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceShaderSMBuiltinsPropertiesNV where
zero :: PhysicalDeviceShaderSMBuiltinsPropertiesNV
zero = Word32 -> Word32 -> PhysicalDeviceShaderSMBuiltinsPropertiesNV
PhysicalDeviceShaderSMBuiltinsPropertiesNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceShaderSMBuiltinsFeaturesNV = PhysicalDeviceShaderSMBuiltinsFeaturesNV
{
PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
shaderSMBuiltins :: Bool }
deriving (Typeable, PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
$c/= :: PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
== :: PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
$c== :: PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderSMBuiltinsFeaturesNV)
#endif
deriving instance Show PhysicalDeviceShaderSMBuiltinsFeaturesNV
instance ToCStruct PhysicalDeviceShaderSMBuiltinsFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> (Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceShaderSMBuiltinsFeaturesNV
x Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p PhysicalDeviceShaderSMBuiltinsFeaturesNV
x (Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO b
f Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p PhysicalDeviceShaderSMBuiltinsFeaturesNV{Bool
shaderSMBuiltins :: Bool
$sel:shaderSMBuiltins:PhysicalDeviceShaderSMBuiltinsFeaturesNV :: PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
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 PhysicalDeviceShaderSMBuiltinsFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSMBuiltins))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
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 PhysicalDeviceShaderSMBuiltinsFeaturesNV
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 PhysicalDeviceShaderSMBuiltinsFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> IO PhysicalDeviceShaderSMBuiltinsFeaturesNV
peekCStruct Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
p = do
Bool32
shaderSMBuiltins <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
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 -> PhysicalDeviceShaderSMBuiltinsFeaturesNV
PhysicalDeviceShaderSMBuiltinsFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
shaderSMBuiltins)
instance Storable PhysicalDeviceShaderSMBuiltinsFeaturesNV where
sizeOf :: PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Int
sizeOf ~PhysicalDeviceShaderSMBuiltinsFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceShaderSMBuiltinsFeaturesNV -> Int
alignment ~PhysicalDeviceShaderSMBuiltinsFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> IO PhysicalDeviceShaderSMBuiltinsFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
-> PhysicalDeviceShaderSMBuiltinsFeaturesNV -> IO ()
poke Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
ptr PhysicalDeviceShaderSMBuiltinsFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceShaderSMBuiltinsFeaturesNV where
zero :: PhysicalDeviceShaderSMBuiltinsFeaturesNV
zero = Bool -> PhysicalDeviceShaderSMBuiltinsFeaturesNV
PhysicalDeviceShaderSMBuiltinsFeaturesNV
forall a. Zero a => a
zero
type NV_SHADER_SM_BUILTINS_SPEC_VERSION = 1
pattern NV_SHADER_SM_BUILTINS_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_SHADER_SM_BUILTINS_SPEC_VERSION :: forall a. Integral a => a
$mNV_SHADER_SM_BUILTINS_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_SHADER_SM_BUILTINS_SPEC_VERSION = 1
type NV_SHADER_SM_BUILTINS_EXTENSION_NAME = "VK_NV_shader_sm_builtins"
pattern NV_SHADER_SM_BUILTINS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_SHADER_SM_BUILTINS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_SHADER_SM_BUILTINS_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_SHADER_SM_BUILTINS_EXTENSION_NAME = "VK_NV_shader_sm_builtins"