{-# language CPP #-}
-- | = Name
--
-- VK_NV_compute_shader_derivatives - device extension
--
-- == VK_NV_compute_shader_derivatives
--
-- [__Name String__]
--     @VK_NV_compute_shader_derivatives@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     202
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Contact__]
--
--     -   Pat Brown
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_compute_shader_derivatives] @nvpbrown%0A<<Here describe the issue or question you have about the VK_NV_compute_shader_derivatives extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-07-19
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/NV/SPV_NV_compute_shader_derivatives.html SPV_NV_compute_shader_derivatives>
--
--     -   This extension provides API support for
--         <https://github.com/KhronosGroup/GLSL/blob/master/extensions/nv/GLSL_NV_compute_shader_derivatives.txt GL_NV_compute_shader_derivatives>
--
-- [__Contributors__]
--
--     -   Pat Brown, NVIDIA
--
-- == Description
--
-- This extension adds Vulkan support for the
-- <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/NV/SPV_NV_compute_shader_derivatives.html SPV_NV_compute_shader_derivatives>
-- SPIR-V extension.
--
-- The SPIR-V extension provides two new execution modes, both of which
-- allow compute shaders to use built-ins that evaluate compute derivatives
-- explicitly or implicitly. Derivatives will be computed via differencing
-- over a 2x2 group of shader invocations. The @DerivativeGroupQuadsNV@
-- execution mode assembles shader invocations into 2x2 groups, where each
-- group has x and y coordinates of the local invocation ID of the form
-- (2m+{0,1}, 2n+{0,1}). The @DerivativeGroupLinearNV@ execution mode
-- assembles shader invocations into 2x2 groups, where each group has local
-- invocation index values of the form 4m+{0,1,2,3}.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceComputeShaderDerivativesFeaturesNV'
--
-- == New Enum Constants
--
-- -   'NV_COMPUTE_SHADER_DERIVATIVES_EXTENSION_NAME'
--
-- -   'NV_COMPUTE_SHADER_DERIVATIVES_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_COMPUTE_SHADER_DERIVATIVES_FEATURES_NV'
--
-- == New SPIR-V Capability
--
-- -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-ComputeDerivativeGroupQuadsNV ComputeDerivativeGroupQuadsNV>
--
-- -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-ComputeDerivativeGroupLinearNV ComputeDerivativeGroupLinearNV>
--
-- == Issues
--
-- (1) Should we specify that the groups of four shader invocations used
-- for derivatives in a compute shader are the same groups of four
-- invocations that form a “quad” in shader subgroups?
--
-- __RESOLVED__: Yes.
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2018-07-19 (Pat Brown)
--
--     -   Initial draft
--
-- == See Also
--
-- 'PhysicalDeviceComputeShaderDerivativesFeaturesNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_compute_shader_derivatives Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
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 (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.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_COMPUTE_SHADER_DERIVATIVES_FEATURES_NV))
-- | VkPhysicalDeviceComputeShaderDerivativesFeaturesNV - Structure
-- describing compute shader derivative features that can be supported by
-- an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-scope-quad Quad shader scope>
-- for more information.
--
-- If the @VkPhysicalDeviceComputeShaderDerivativesFeaturesNVfeatures@.
-- 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. @VkPhysicalDeviceComputeShaderDerivativesFeaturesNVfeatures@.
-- /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_NV_compute_shader_derivatives VK_NV_compute_shader_derivatives>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceComputeShaderDerivativesFeaturesNV = PhysicalDeviceComputeShaderDerivativesFeaturesNV
  { -- | #features-computeDerivativeGroupQuads# @computeDerivativeGroupQuads@
    -- indicates that the implementation supports the
    -- @ComputeDerivativeGroupQuadsNV@ SPIR-V capability.
    PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
computeDerivativeGroupQuads :: Bool
  , -- | #features-computeDerivativeGroupLinear# @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 PhysicalDeviceComputeShaderDerivativesFeaturesNV
x Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV
p PhysicalDeviceComputeShaderDerivativesFeaturesNV{Bool
computeDerivativeGroupLinear :: Bool
computeDerivativeGroupQuads :: Bool
$sel:computeDerivativeGroupLinear:PhysicalDeviceComputeShaderDerivativesFeaturesNV :: PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
$sel:computeDerivativeGroupQuads:PhysicalDeviceComputeShaderDerivativesFeaturesNV :: PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Bool
..} 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` Int
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` Int
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` Int
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` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
computeDerivativeGroupLinear))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceComputeShaderDerivativesFeaturesNV
p 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` Int
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` Int
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` Int
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` Int
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 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` Int
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` Int
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
_ = Int
24
  alignment :: PhysicalDeviceComputeShaderDerivativesFeaturesNV -> Int
alignment ~PhysicalDeviceComputeShaderDerivativesFeaturesNV
_ = Int
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 PhysicalDeviceComputeShaderDerivativesFeaturesNV
ptr 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"