{-# language CPP #-}
-- | = Name
--
-- VK_NV_device_diagnostics_config - device extension
--
-- == VK_NV_device_diagnostics_config
--
-- [__Name String__]
--     @VK_NV_device_diagnostics_config@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     301
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Contact__]
--
--     -   Kedarnath Thangudu
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_device_diagnostics_config] @kthangudu%0A<<Here describe the issue or question you have about the VK_NV_device_diagnostics_config extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-12-15
--
-- [__Contributors__]
--
--     -   Kedarnath Thangudu, NVIDIA
--
--     -   Thomas Klein, NVIDIA
--
-- == Description
--
-- Applications using Nvidia Nsight™ Aftermath SDK for Vulkan to integrate
-- device crash dumps into their error reporting mechanisms, /may/ use this
-- extension to configure options related to device crash dump creation.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'DeviceDiagnosticsConfigCreateInfoNV'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceDiagnosticsConfigFeaturesNV'
--
-- == New Enums
--
-- -   'DeviceDiagnosticsConfigFlagBitsNV'
--
-- == New Bitmasks
--
-- -   'DeviceDiagnosticsConfigFlagsNV'
--
-- == New Enum Constants
--
-- -   'NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME'
--
-- -   'NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV'
--
-- == Version History
--
-- -   Revision 1, 2019-11-21 (Kedarnath Thangudu)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'DeviceDiagnosticsConfigCreateInfoNV',
-- 'DeviceDiagnosticsConfigFlagBitsNV', 'DeviceDiagnosticsConfigFlagsNV',
-- 'PhysicalDeviceDiagnosticsConfigFeaturesNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_device_diagnostics_config 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_device_diagnostics_config  ( PhysicalDeviceDiagnosticsConfigFeaturesNV(..)
                                                          , DeviceDiagnosticsConfigCreateInfoNV(..)
                                                          , DeviceDiagnosticsConfigFlagsNV
                                                          , DeviceDiagnosticsConfigFlagBitsNV( DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV
                                                                                             , DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV
                                                                                             , DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV
                                                                                             , ..
                                                                                             )
                                                          , NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION
                                                          , pattern NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION
                                                          , NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME
                                                          , pattern NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME
                                                          ) where

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.Bits (Bits)
import Data.Bits (FiniteBits)
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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV))
-- | VkPhysicalDeviceDiagnosticsConfigFeaturesNV - Structure describing the
-- device-generated diagnostic configuration features that can be supported
-- by an implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceDiagnosticsConfigFeaturesNV' 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. 'PhysicalDeviceDiagnosticsConfigFeaturesNV' /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_device_diagnostics_config VK_NV_device_diagnostics_config>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDiagnosticsConfigFeaturesNV = PhysicalDeviceDiagnosticsConfigFeaturesNV
  { -- | #features-diagnosticsConfig# @diagnosticsConfig@ indicates whether the
    -- implementation supports the ability to configure diagnostic tools.
    PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
diagnosticsConfig :: Bool }
  deriving (Typeable, PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
(PhysicalDeviceDiagnosticsConfigFeaturesNV
 -> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool)
-> (PhysicalDeviceDiagnosticsConfigFeaturesNV
    -> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool)
-> Eq PhysicalDeviceDiagnosticsConfigFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
$c/= :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
== :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
$c== :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDiagnosticsConfigFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDiagnosticsConfigFeaturesNV

instance ToCStruct PhysicalDeviceDiagnosticsConfigFeaturesNV where
  withCStruct :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceDiagnosticsConfigFeaturesNV
x Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p -> Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p PhysicalDeviceDiagnosticsConfigFeaturesNV
x (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b
f Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p)
  pokeCStruct :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p PhysicalDeviceDiagnosticsConfigFeaturesNV{Bool
diagnosticsConfig :: Bool
$sel:diagnosticsConfig:PhysicalDeviceDiagnosticsConfigFeaturesNV :: PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> 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 PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
diagnosticsConfig))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> 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 PhysicalDeviceDiagnosticsConfigFeaturesNV
p Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> 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))
    IO b
f

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

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

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


-- | VkDeviceDiagnosticsConfigCreateInfoNV - Specify diagnostics config for a
-- Vulkan device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_device_diagnostics_config VK_NV_device_diagnostics_config>,
-- 'DeviceDiagnosticsConfigFlagsNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceDiagnosticsConfigCreateInfoNV = DeviceDiagnosticsConfigCreateInfoNV
  { -- | @flags@ is a bitmask of 'DeviceDiagnosticsConfigFlagBitsNV' specifying
    -- addtional parameters for configuring diagnostic tools.
    --
    -- #VUID-VkDeviceDiagnosticsConfigCreateInfoNV-flags-parameter# @flags@
    -- /must/ be a valid combination of 'DeviceDiagnosticsConfigFlagBitsNV'
    -- values
    DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigFlagsNV
flags :: DeviceDiagnosticsConfigFlagsNV }
  deriving (Typeable, DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
(DeviceDiagnosticsConfigCreateInfoNV
 -> DeviceDiagnosticsConfigCreateInfoNV -> Bool)
-> (DeviceDiagnosticsConfigCreateInfoNV
    -> DeviceDiagnosticsConfigCreateInfoNV -> Bool)
-> Eq DeviceDiagnosticsConfigCreateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
$c/= :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
== :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
$c== :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceDiagnosticsConfigCreateInfoNV)
#endif
deriving instance Show DeviceDiagnosticsConfigCreateInfoNV

instance ToCStruct DeviceDiagnosticsConfigCreateInfoNV where
  withCStruct :: DeviceDiagnosticsConfigCreateInfoNV
-> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
withCStruct DeviceDiagnosticsConfigCreateInfoNV
x Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b
f = Int -> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b)
-> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DeviceDiagnosticsConfigCreateInfoNV
p -> Ptr DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
p DeviceDiagnosticsConfigCreateInfoNV
x (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b
f Ptr DeviceDiagnosticsConfigCreateInfoNV
p)
  pokeCStruct :: Ptr DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
p DeviceDiagnosticsConfigCreateInfoNV{DeviceDiagnosticsConfigFlagsNV
flags :: DeviceDiagnosticsConfigFlagsNV
$sel:flags:DeviceDiagnosticsConfigCreateInfoNV :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigFlagsNV
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV
-> Int -> Ptr DeviceDiagnosticsConfigFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceDiagnosticsConfigFlagsNV)) (DeviceDiagnosticsConfigFlagsNV
flags)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct DeviceDiagnosticsConfigCreateInfoNV where
  peekCStruct :: Ptr DeviceDiagnosticsConfigCreateInfoNV
-> IO DeviceDiagnosticsConfigCreateInfoNV
peekCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
p = do
    DeviceDiagnosticsConfigFlagsNV
flags <- Ptr DeviceDiagnosticsConfigFlagsNV
-> IO DeviceDiagnosticsConfigFlagsNV
forall a. Storable a => Ptr a -> IO a
peek @DeviceDiagnosticsConfigFlagsNV ((Ptr DeviceDiagnosticsConfigCreateInfoNV
p Ptr DeviceDiagnosticsConfigCreateInfoNV
-> Int -> Ptr DeviceDiagnosticsConfigFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceDiagnosticsConfigFlagsNV))
    DeviceDiagnosticsConfigCreateInfoNV
-> IO DeviceDiagnosticsConfigCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceDiagnosticsConfigCreateInfoNV
 -> IO DeviceDiagnosticsConfigCreateInfoNV)
-> DeviceDiagnosticsConfigCreateInfoNV
-> IO DeviceDiagnosticsConfigCreateInfoNV
forall a b. (a -> b) -> a -> b
$ DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigCreateInfoNV
DeviceDiagnosticsConfigCreateInfoNV
             DeviceDiagnosticsConfigFlagsNV
flags

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

instance Zero DeviceDiagnosticsConfigCreateInfoNV where
  zero :: DeviceDiagnosticsConfigCreateInfoNV
zero = DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigCreateInfoNV
DeviceDiagnosticsConfigCreateInfoNV
           DeviceDiagnosticsConfigFlagsNV
forall a. Zero a => a
zero


type DeviceDiagnosticsConfigFlagsNV = DeviceDiagnosticsConfigFlagBitsNV

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

-- | 'DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV' enables the
-- generation of debug information for shaders.
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV :: forall r.
DeviceDiagnosticsConfigFlagsNV -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV     = DeviceDiagnosticsConfigFlagBitsNV 0x00000001
-- | 'DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV' enables
-- driver side tracking of resources (images, buffers, etc.) used to
-- augment the device fault information.
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV :: forall r.
DeviceDiagnosticsConfigFlagsNV -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV     = DeviceDiagnosticsConfigFlagBitsNV 0x00000002
-- | 'DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV' enables
-- automatic insertion of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#device-diagnostic-checkpoints diagnostic checkpoints>
-- for draw calls, dispatches, trace rays, and copies. The CPU call stack
-- at the time of the command will be associated as the marker data for the
-- automatically inserted checkpoints.
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV :: forall r.
DeviceDiagnosticsConfigFlagsNV -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV = DeviceDiagnosticsConfigFlagBitsNV 0x00000004

conNameDeviceDiagnosticsConfigFlagBitsNV :: String
conNameDeviceDiagnosticsConfigFlagBitsNV :: String
conNameDeviceDiagnosticsConfigFlagBitsNV = String
"DeviceDiagnosticsConfigFlagBitsNV"

enumPrefixDeviceDiagnosticsConfigFlagBitsNV :: String
enumPrefixDeviceDiagnosticsConfigFlagBitsNV :: String
enumPrefixDeviceDiagnosticsConfigFlagBitsNV = String
"DEVICE_DIAGNOSTICS_CONFIG_ENABLE_"

showTableDeviceDiagnosticsConfigFlagBitsNV :: [(DeviceDiagnosticsConfigFlagBitsNV, String)]
showTableDeviceDiagnosticsConfigFlagBitsNV :: [(DeviceDiagnosticsConfigFlagsNV, String)]
showTableDeviceDiagnosticsConfigFlagBitsNV =
  [ (DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV    , String
"SHADER_DEBUG_INFO_BIT_NV")
  , (DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV    , String
"RESOURCE_TRACKING_BIT_NV")
  , (DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV, String
"AUTOMATIC_CHECKPOINTS_BIT_NV")
  ]

instance Show DeviceDiagnosticsConfigFlagBitsNV where
  showsPrec :: Int -> DeviceDiagnosticsConfigFlagsNV -> ShowS
showsPrec = String
-> [(DeviceDiagnosticsConfigFlagsNV, String)]
-> String
-> (DeviceDiagnosticsConfigFlagsNV -> Flags)
-> (Flags -> ShowS)
-> Int
-> DeviceDiagnosticsConfigFlagsNV
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDeviceDiagnosticsConfigFlagBitsNV
                            [(DeviceDiagnosticsConfigFlagsNV, String)]
showTableDeviceDiagnosticsConfigFlagBitsNV
                            String
conNameDeviceDiagnosticsConfigFlagBitsNV
                            (\(DeviceDiagnosticsConfigFlagBitsNV Flags
x) -> Flags
x)
                            (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read DeviceDiagnosticsConfigFlagBitsNV where
  readPrec :: ReadPrec DeviceDiagnosticsConfigFlagsNV
readPrec = String
-> [(DeviceDiagnosticsConfigFlagsNV, String)]
-> String
-> (Flags -> DeviceDiagnosticsConfigFlagsNV)
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDeviceDiagnosticsConfigFlagBitsNV
                          [(DeviceDiagnosticsConfigFlagsNV, String)]
showTableDeviceDiagnosticsConfigFlagBitsNV
                          String
conNameDeviceDiagnosticsConfigFlagBitsNV
                          Flags -> DeviceDiagnosticsConfigFlagsNV
DeviceDiagnosticsConfigFlagBitsNV


type NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION"
pattern NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: a
$mNV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION = 1


type NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME = "VK_NV_device_diagnostics_config"

-- No documentation found for TopLevel "VK_NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME"
pattern NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: a
$mNV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME = "VK_NV_device_diagnostics_config"