{-# language CPP #-}
module Vulkan.Extensions.VK_NV_compute_shader_derivatives  ( PhysicalDeviceComputeShaderDerivativesFeaturesNV(..)
                                                           , NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION
                                                           , pattern NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION
                                                           , NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME
                                                           , pattern NV_COMPUTE_SHADER_DERIVATIVES_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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
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_COMPUTE_SHADER_DERIVATIVES_FEATURES_NV))
-- | VkPhysicalDeviceComputeShaderDerivativesFeaturesNV - Structure
-- describing compute shader derivative features that can be supported by
-- an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceComputeShaderDerivativesFeaturesNV'
-- structure describe the following features:
--
-- = Description
--
-- See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-scope-quad>
-- chapter for more information.
--
-- If the 'PhysicalDeviceComputeShaderDerivativesFeaturesNV' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether each feature is supported.
-- 'PhysicalDeviceComputeShaderDerivativesFeaturesNV' /can/ also be
-- included in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo'
-- to enable features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceComputeShaderDerivativesFeaturesNV = PhysicalDeviceComputeShaderDerivativesFeaturesNV
  { -- | @computeDerivativeGroupQuads@ indicates that the implementation supports
    -- the @ComputeDerivativeGroupQuadsNV@ SPIR-V capability.
    PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
computeDerivativeGroupQuads :: Bool
  , -- | @computeDerivativeGroupLinear@ indicates that the implementation
    -- supports the @ComputeDerivativeGroupLinearNV@ SPIR-V capability.
    PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
computeDerivativeGroupLinear :: Bool
  }
  deriving (Typeable, PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
(PhysicalDeviceComputeShaderDerivativesFeaturesNV
 -> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool)
-> (PhysicalDeviceComputeShaderDerivativesFeaturesNV
    -> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool)
-> Eq PhysicalDeviceComputeShaderDerivativesFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
$c/= :: PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
== :: PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
$c== :: PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceComputeShaderDerivativesFeaturesNV)
#endif
deriving instance Show PhysicalDeviceComputeShaderDerivativesFeaturesNV

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

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

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

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


type NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION"
pattern NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION :: a
$mNV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION = 1


type NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME = "VK_NV_compute_shader_derivatives"

-- No documentation found for TopLevel "VK_NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME"
pattern NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME :: a
$mNV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME = "VK_NV_compute_shader_derivatives"