{-# language CPP #-}
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
, DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_ERROR_REPORTING_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 Data.Bits (Bits)
import Data.Bits (FiniteBits)
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.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))
data PhysicalDeviceDiagnosticsConfigFeaturesNV = PhysicalDeviceDiagnosticsConfigFeaturesNV
{
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
$c== :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
== :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
$c/= :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
/= :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDiagnosticsConfigFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDiagnosticsConfigFeaturesNV
instance ToCStruct PhysicalDeviceDiagnosticsConfigFeaturesNV where
withCStruct :: forall b.
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 b.
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 :: forall b.
Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p PhysicalDeviceDiagnosticsConfigFeaturesNV{Bool
$sel:diagnosticsConfig:PhysicalDeviceDiagnosticsConfigFeaturesNV :: PhysicalDeviceDiagnosticsConfigFeaturesNV -> Bool
diagnosticsConfig :: 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 :: forall b.
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 <- 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 a. a -> IO a
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 b.
Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
-> PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
poked (() -> IO ()
forall a. a -> IO a
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
data DeviceDiagnosticsConfigCreateInfoNV = DeviceDiagnosticsConfigCreateInfoNV
{
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
$c== :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
== :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
$c/= :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
/= :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceDiagnosticsConfigCreateInfoNV)
#endif
deriving instance Show DeviceDiagnosticsConfigCreateInfoNV
instance ToCStruct DeviceDiagnosticsConfigCreateInfoNV where
withCStruct :: forall b.
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 b.
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 :: forall b.
Ptr DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
p DeviceDiagnosticsConfigCreateInfoNV{DeviceDiagnosticsConfigFlagsNV
$sel:flags:DeviceDiagnosticsConfigCreateInfoNV :: DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigFlagsNV
flags :: 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 :: forall b. 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 <- 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 a. a -> IO a
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 b.
Ptr DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceDiagnosticsConfigCreateInfoNV
ptr DeviceDiagnosticsConfigCreateInfoNV
poked (() -> IO ()
forall a. a -> IO a
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
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
$c== :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Bool
== :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Bool
$c/= :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Bool
/= :: 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
$ccompare :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Ordering
compare :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Ordering
$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
>= :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> Bool
$cmax :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
max :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
$cmin :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
min :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
Ord, 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
$csizeOf :: DeviceDiagnosticsConfigFlagsNV -> Int
sizeOf :: DeviceDiagnosticsConfigFlagsNV -> Int
$calignment :: DeviceDiagnosticsConfigFlagsNV -> Int
alignment :: DeviceDiagnosticsConfigFlagsNV -> Int
$cpeekElemOff :: Ptr DeviceDiagnosticsConfigFlagsNV
-> Int -> IO DeviceDiagnosticsConfigFlagsNV
peekElemOff :: Ptr DeviceDiagnosticsConfigFlagsNV
-> Int -> IO DeviceDiagnosticsConfigFlagsNV
$cpokeElemOff :: Ptr DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV -> IO ()
pokeElemOff :: Ptr DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceDiagnosticsConfigFlagsNV
peekByteOff :: forall b. Ptr b -> Int -> IO DeviceDiagnosticsConfigFlagsNV
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceDiagnosticsConfigFlagsNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DeviceDiagnosticsConfigFlagsNV -> IO ()
$cpeek :: Ptr DeviceDiagnosticsConfigFlagsNV
-> IO DeviceDiagnosticsConfigFlagsNV
peek :: Ptr DeviceDiagnosticsConfigFlagsNV
-> IO DeviceDiagnosticsConfigFlagsNV
$cpoke :: Ptr DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> IO ()
poke :: Ptr DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> IO ()
Storable, DeviceDiagnosticsConfigFlagsNV
DeviceDiagnosticsConfigFlagsNV
-> Zero DeviceDiagnosticsConfigFlagsNV
forall a. a -> Zero a
$czero :: DeviceDiagnosticsConfigFlagsNV
zero :: 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
$c.&. :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
.&. :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
$c.|. :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
.|. :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
$cxor :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
xor :: DeviceDiagnosticsConfigFlagsNV
-> DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
$ccomplement :: DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
complement :: DeviceDiagnosticsConfigFlagsNV -> DeviceDiagnosticsConfigFlagsNV
$cshift :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
shift :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$crotate :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
rotate :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$czeroBits :: DeviceDiagnosticsConfigFlagsNV
zeroBits :: DeviceDiagnosticsConfigFlagsNV
$cbit :: Int -> DeviceDiagnosticsConfigFlagsNV
bit :: Int -> DeviceDiagnosticsConfigFlagsNV
$csetBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
setBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$cclearBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
clearBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$ccomplementBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
complementBit :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$ctestBit :: DeviceDiagnosticsConfigFlagsNV -> Int -> Bool
testBit :: DeviceDiagnosticsConfigFlagsNV -> Int -> Bool
$cbitSizeMaybe :: DeviceDiagnosticsConfigFlagsNV -> Maybe Int
bitSizeMaybe :: DeviceDiagnosticsConfigFlagsNV -> Maybe Int
$cbitSize :: DeviceDiagnosticsConfigFlagsNV -> Int
bitSize :: DeviceDiagnosticsConfigFlagsNV -> Int
$cisSigned :: DeviceDiagnosticsConfigFlagsNV -> Bool
isSigned :: DeviceDiagnosticsConfigFlagsNV -> Bool
$cshiftL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
shiftL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$cunsafeShiftL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
unsafeShiftL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$cshiftR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
shiftR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$cunsafeShiftR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
unsafeShiftR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$crotateL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
rotateL :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$crotateR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
rotateR :: DeviceDiagnosticsConfigFlagsNV
-> Int -> DeviceDiagnosticsConfigFlagsNV
$cpopCount :: DeviceDiagnosticsConfigFlagsNV -> Int
popCount :: DeviceDiagnosticsConfigFlagsNV -> Int
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
$cfiniteBitSize :: DeviceDiagnosticsConfigFlagsNV -> Int
finiteBitSize :: DeviceDiagnosticsConfigFlagsNV -> Int
$ccountLeadingZeros :: DeviceDiagnosticsConfigFlagsNV -> Int
countLeadingZeros :: DeviceDiagnosticsConfigFlagsNV -> Int
$ccountTrailingZeros :: DeviceDiagnosticsConfigFlagsNV -> Int
countTrailingZeros :: DeviceDiagnosticsConfigFlagsNV -> Int
FiniteBits)
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV :: forall {r}.
DeviceDiagnosticsConfigFlagsNV -> ((# #) -> r) -> ((# #) -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV = DeviceDiagnosticsConfigFlagBitsNV 0x00000001
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV :: forall {r}.
DeviceDiagnosticsConfigFlagsNV -> ((# #) -> r) -> ((# #) -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV = DeviceDiagnosticsConfigFlagBitsNV 0x00000002
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV :: forall {r}.
DeviceDiagnosticsConfigFlagsNV -> ((# #) -> r) -> ((# #) -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV = DeviceDiagnosticsConfigFlagBitsNV 0x00000004
pattern $bDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_ERROR_REPORTING_BIT_NV :: DeviceDiagnosticsConfigFlagsNV
$mDEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_ERROR_REPORTING_BIT_NV :: forall {r}.
DeviceDiagnosticsConfigFlagsNV -> ((# #) -> r) -> ((# #) -> r) -> r
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_ERROR_REPORTING_BIT_NV = DeviceDiagnosticsConfigFlagBitsNV 0x00000008
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"
)
,
( DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_ERROR_REPORTING_BIT_NV
, String
"SHADER_ERROR_REPORTING_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 => 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 = 2
pattern NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: forall a. Integral a => a
$mNV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION = 2
type NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME = "VK_NV_device_diagnostics_config"
pattern NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEVICE_DIAGNOSTICS_CONFIG_EXTENSION_NAME = "VK_NV_device_diagnostics_config"