{-# language CPP #-}
module Vulkan.Extensions.VK_NV_device_diagnostics_config ( PhysicalDeviceDiagnosticsConfigFeaturesNV(..)
, DeviceDiagnosticsConfigCreateInfoNV(..)
, 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
, ..
)
, DeviceDiagnosticsConfigFlagsNV
, 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 Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
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 Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.BaseType (Flags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
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)
deriving instance Show PhysicalDeviceDiagnosticsConfigFeaturesNV
instance ToCStruct PhysicalDeviceDiagnosticsConfigFeaturesNV where
withCStruct :: PhysicalDeviceDiagnosticsConfigFeaturesNV
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b
withCStruct x :: PhysicalDeviceDiagnosticsConfigFeaturesNV
x f :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p PhysicalDeviceDiagnosticsConfigFeaturesNV{..} f :: 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` 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` 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` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
diagnosticsConfig))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
p f :: 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` 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` 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` 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 p :: 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` 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
_ = 24
alignment :: PhysicalDeviceDiagnosticsConfigFeaturesNV -> Int
alignment ~PhysicalDeviceDiagnosticsConfigFeaturesNV
_ = 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 :: Ptr PhysicalDeviceDiagnosticsConfigFeaturesNV
ptr poked :: 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
data DeviceDiagnosticsConfigCreateInfoNV = DeviceDiagnosticsConfigCreateInfoNV
{
DeviceDiagnosticsConfigCreateInfoNV
-> DeviceDiagnosticsConfigFlagsNV
flags :: DeviceDiagnosticsConfigFlagsNV }
deriving (Typeable)
deriving instance Show DeviceDiagnosticsConfigCreateInfoNV
instance ToCStruct DeviceDiagnosticsConfigCreateInfoNV where
withCStruct :: DeviceDiagnosticsConfigCreateInfoNV
-> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
withCStruct x :: DeviceDiagnosticsConfigCreateInfoNV
x f :: Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b
f = Int
-> Int -> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b)
-> (Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr DeviceDiagnosticsConfigCreateInfoNV
p DeviceDiagnosticsConfigCreateInfoNV{..} f :: 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` 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` 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` 16 :: Ptr DeviceDiagnosticsConfigFlagsNV)) (DeviceDiagnosticsConfigFlagsNV
flags)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DeviceDiagnosticsConfigCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceDiagnosticsConfigCreateInfoNV
p f :: 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` 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` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct DeviceDiagnosticsConfigCreateInfoNV where
peekCStruct :: Ptr DeviceDiagnosticsConfigCreateInfoNV
-> IO DeviceDiagnosticsConfigCreateInfoNV
peekCStruct p :: 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` 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
_ = 24
alignment :: DeviceDiagnosticsConfigCreateInfoNV -> Int
alignment ~DeviceDiagnosticsConfigCreateInfoNV
_ = 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 :: Ptr DeviceDiagnosticsConfigCreateInfoNV
ptr poked :: 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
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)
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
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
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
type DeviceDiagnosticsConfigFlagsNV = DeviceDiagnosticsConfigFlagBitsNV
instance Show DeviceDiagnosticsConfigFlagBitsNV where
showsPrec :: Int -> DeviceDiagnosticsConfigFlagsNV -> ShowS
showsPrec p :: Int
p = \case
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV -> String -> ShowS
showString "DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV"
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV -> String -> ShowS
showString "DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV"
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV -> String -> ShowS
showString "DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV"
DeviceDiagnosticsConfigFlagBitsNV x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DeviceDiagnosticsConfigFlagBitsNV 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 = ReadPrec DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DeviceDiagnosticsConfigFlagsNV)]
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV", DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_SHADER_DEBUG_INFO_BIT_NV)
, ("DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV", DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_RESOURCE_TRACKING_BIT_NV)
, ("DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV", DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure DeviceDiagnosticsConfigFlagsNV
DEVICE_DIAGNOSTICS_CONFIG_ENABLE_AUTOMATIC_CHECKPOINTS_BIT_NV)]
ReadPrec DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DeviceDiagnosticsConfigFlagBitsNV")
Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
DeviceDiagnosticsConfigFlagsNV
-> ReadPrec DeviceDiagnosticsConfigFlagsNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> DeviceDiagnosticsConfigFlagsNV
DeviceDiagnosticsConfigFlagBitsNV Flags
v)))
type NV_DEVICE_DIAGNOSTICS_CONFIG_SPEC_VERSION = 1
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"
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"