{-# language CPP #-}
module Vulkan.Extensions.Handles ( IndirectCommandsLayoutNV(..)
, ValidationCacheEXT(..)
, AccelerationStructureKHR(..)
, AccelerationStructureNV(..)
, PerformanceConfigurationINTEL(..)
, BufferCollectionFUCHSIA(..)
, DeferredOperationKHR(..)
, CuModuleNVX(..)
, CuFunctionNVX(..)
, OpticalFlowSessionNV(..)
, MicromapEXT(..)
, ShaderEXT(..)
, DisplayKHR(..)
, DisplayModeKHR(..)
, SurfaceKHR(..)
, SwapchainKHR(..)
, DebugReportCallbackEXT(..)
, DebugUtilsMessengerEXT(..)
, Instance(..)
, PhysicalDevice(..)
, Device(..)
, Queue(..)
, CommandBuffer(..)
, DeviceMemory(..)
, CommandPool(..)
, Buffer(..)
, BufferView(..)
, Image(..)
, ImageView(..)
, ShaderModule(..)
, Pipeline(..)
, PipelineLayout(..)
, Sampler(..)
, DescriptorSet(..)
, DescriptorSetLayout(..)
, Fence(..)
, Semaphore(..)
, Event(..)
, QueryPool(..)
, Framebuffer(..)
, RenderPass(..)
, PipelineCache(..)
, DescriptorUpdateTemplate(..)
, SamplerYcbcrConversion(..)
, PrivateDataSlot(..)
) where
import GHC.Show (showParen)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Word (Word64)
import Vulkan.Core10.APIConstants (HasObjectType(..))
import Vulkan.Core10.APIConstants (IsHandle)
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_ACCELERATION_STRUCTURE_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CU_FUNCTION_NVX))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CU_MODULE_NVX))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEFERRED_OPERATION_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DISPLAY_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DISPLAY_MODE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_MICROMAP_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_OPTICAL_FLOW_SESSION_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SHADER_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SURFACE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SWAPCHAIN_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_VALIDATION_CACHE_EXT))
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.Core10.Handles (BufferView(..))
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandPool(..))
import Vulkan.Core10.Handles (DescriptorSet(..))
import Vulkan.Core10.Handles (DescriptorSetLayout(..))
import Vulkan.Core11.Handles (DescriptorUpdateTemplate(..))
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (DeviceMemory(..))
import Vulkan.Core10.Handles (Event(..))
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.Core10.Handles (Framebuffer(..))
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Handles (ImageView(..))
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Handles (PipelineCache(..))
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.Core13.Handles (PrivateDataSlot(..))
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (RenderPass(..))
import Vulkan.Core10.Handles (Sampler(..))
import Vulkan.Core11.Handles (SamplerYcbcrConversion(..))
import Vulkan.Core10.Handles (Semaphore(..))
import Vulkan.Core10.Handles (ShaderModule(..))
newtype IndirectCommandsLayoutNV = IndirectCommandsLayoutNV Word64
deriving newtype (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
== :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c== :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
Eq, Eq IndirectCommandsLayoutNV
IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
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 :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
$cmin :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
max :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
$cmax :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
>= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c>= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
> :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c> :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
<= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c<= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
< :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c< :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
compare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
$ccompare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
Ord, Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
IndirectCommandsLayoutNV -> Int
forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> 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 IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
$cpoke :: Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
peek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
$cpeek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
pokeByteOff :: forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
pokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
$cpokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
peekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
$cpeekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
alignment :: IndirectCommandsLayoutNV -> Int
$calignment :: IndirectCommandsLayoutNV -> Int
sizeOf :: IndirectCommandsLayoutNV -> Int
$csizeOf :: IndirectCommandsLayoutNV -> Int
Storable, IndirectCommandsLayoutNV
forall a. a -> Zero a
zero :: IndirectCommandsLayoutNV
$czero :: IndirectCommandsLayoutNV
Zero)
deriving anyclass (Eq IndirectCommandsLayoutNV
Zero IndirectCommandsLayoutNV
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType IndirectCommandsLayoutNV where
objectTypeAndHandle :: IndirectCommandsLayoutNV -> (ObjectType, Word64)
objectTypeAndHandle (IndirectCommandsLayoutNV Word64
h) = ( ObjectType
OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV
, Word64
h )
instance Show IndirectCommandsLayoutNV where
showsPrec :: Int -> IndirectCommandsLayoutNV -> ShowS
showsPrec Int
p (IndirectCommandsLayoutNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"IndirectCommandsLayoutNV 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype ValidationCacheEXT = ValidationCacheEXT Word64
deriving newtype (ValidationCacheEXT -> ValidationCacheEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
== :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c== :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
Eq, Eq ValidationCacheEXT
ValidationCacheEXT -> ValidationCacheEXT -> Bool
ValidationCacheEXT -> ValidationCacheEXT -> Ordering
ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
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 :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
$cmin :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
max :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
$cmax :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
>= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c>= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
> :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c> :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
<= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c<= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
< :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c< :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
compare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
$ccompare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
Ord, Ptr ValidationCacheEXT -> IO ValidationCacheEXT
Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
ValidationCacheEXT -> Int
forall b. Ptr b -> Int -> IO ValidationCacheEXT
forall b. Ptr b -> Int -> ValidationCacheEXT -> 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 ValidationCacheEXT -> ValidationCacheEXT -> IO ()
$cpoke :: Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
peek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
$cpeek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
pokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheEXT
pokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
$cpokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
peekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
$cpeekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
alignment :: ValidationCacheEXT -> Int
$calignment :: ValidationCacheEXT -> Int
sizeOf :: ValidationCacheEXT -> Int
$csizeOf :: ValidationCacheEXT -> Int
Storable, ValidationCacheEXT
forall a. a -> Zero a
zero :: ValidationCacheEXT
$czero :: ValidationCacheEXT
Zero)
deriving anyclass (Eq ValidationCacheEXT
Zero ValidationCacheEXT
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType ValidationCacheEXT where
objectTypeAndHandle :: ValidationCacheEXT -> (ObjectType, Word64)
objectTypeAndHandle (ValidationCacheEXT Word64
h) = ( ObjectType
OBJECT_TYPE_VALIDATION_CACHE_EXT
, Word64
h )
instance Show ValidationCacheEXT where
showsPrec :: Int -> ValidationCacheEXT -> ShowS
showsPrec Int
p (ValidationCacheEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"ValidationCacheEXT 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype AccelerationStructureKHR = AccelerationStructureKHR Word64
deriving newtype (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
== :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c== :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
Eq, Eq AccelerationStructureKHR
AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
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 :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
$cmin :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
max :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
$cmax :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
>= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c>= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
> :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c> :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
<= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c<= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
< :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c< :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
compare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
$ccompare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
Ord, Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
AccelerationStructureKHR -> Int
forall b. Ptr b -> Int -> IO AccelerationStructureKHR
forall b. Ptr b -> Int -> AccelerationStructureKHR -> 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 AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
$cpoke :: Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
peek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
$cpeek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
pokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureKHR
pokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
peekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
$cpeekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
alignment :: AccelerationStructureKHR -> Int
$calignment :: AccelerationStructureKHR -> Int
sizeOf :: AccelerationStructureKHR -> Int
$csizeOf :: AccelerationStructureKHR -> Int
Storable, AccelerationStructureKHR
forall a. a -> Zero a
zero :: AccelerationStructureKHR
$czero :: AccelerationStructureKHR
Zero)
deriving anyclass (Eq AccelerationStructureKHR
Zero AccelerationStructureKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType AccelerationStructureKHR where
objectTypeAndHandle :: AccelerationStructureKHR -> (ObjectType, Word64)
objectTypeAndHandle (AccelerationStructureKHR Word64
h) = ( ObjectType
OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR
, Word64
h )
instance Show AccelerationStructureKHR where
showsPrec :: Int -> AccelerationStructureKHR -> ShowS
showsPrec Int
p (AccelerationStructureKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"AccelerationStructureKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype AccelerationStructureNV = AccelerationStructureNV Word64
deriving newtype (AccelerationStructureNV -> AccelerationStructureNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c/= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
== :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c== :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
Eq, Eq AccelerationStructureNV
AccelerationStructureNV -> AccelerationStructureNV -> Bool
AccelerationStructureNV -> AccelerationStructureNV -> Ordering
AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
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 :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
$cmin :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
max :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
$cmax :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
>= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c>= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
> :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c> :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
<= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c<= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
< :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c< :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
compare :: AccelerationStructureNV -> AccelerationStructureNV -> Ordering
$ccompare :: AccelerationStructureNV -> AccelerationStructureNV -> Ordering
Ord, Ptr AccelerationStructureNV -> IO AccelerationStructureNV
Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
Ptr AccelerationStructureNV -> AccelerationStructureNV -> IO ()
AccelerationStructureNV -> Int
forall b. Ptr b -> Int -> IO AccelerationStructureNV
forall b. Ptr b -> Int -> AccelerationStructureNV -> 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 AccelerationStructureNV -> AccelerationStructureNV -> IO ()
$cpoke :: Ptr AccelerationStructureNV -> AccelerationStructureNV -> IO ()
peek :: Ptr AccelerationStructureNV -> IO AccelerationStructureNV
$cpeek :: Ptr AccelerationStructureNV -> IO AccelerationStructureNV
pokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureNV -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureNV
pokeElemOff :: Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
peekElemOff :: Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
$cpeekElemOff :: Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
alignment :: AccelerationStructureNV -> Int
$calignment :: AccelerationStructureNV -> Int
sizeOf :: AccelerationStructureNV -> Int
$csizeOf :: AccelerationStructureNV -> Int
Storable, AccelerationStructureNV
forall a. a -> Zero a
zero :: AccelerationStructureNV
$czero :: AccelerationStructureNV
Zero)
deriving anyclass (Eq AccelerationStructureNV
Zero AccelerationStructureNV
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType AccelerationStructureNV where
objectTypeAndHandle :: AccelerationStructureNV -> (ObjectType, Word64)
objectTypeAndHandle (AccelerationStructureNV Word64
h) = ( ObjectType
OBJECT_TYPE_ACCELERATION_STRUCTURE_NV
, Word64
h )
instance Show AccelerationStructureNV where
showsPrec :: Int -> AccelerationStructureNV -> ShowS
showsPrec Int
p (AccelerationStructureNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"AccelerationStructureNV 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype PerformanceConfigurationINTEL = PerformanceConfigurationINTEL Word64
deriving newtype (PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
== :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c== :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
Eq, Eq PerformanceConfigurationINTEL
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
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 :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
$cmin :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
max :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
$cmax :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
>= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c>= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
> :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c> :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
<= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c<= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
< :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c< :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
compare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
$ccompare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
Ord, Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
PerformanceConfigurationINTEL -> Int
forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> 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 PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
$cpoke :: Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
peek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
$cpeek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
pokeByteOff :: forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
pokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
peekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
$cpeekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
alignment :: PerformanceConfigurationINTEL -> Int
$calignment :: PerformanceConfigurationINTEL -> Int
sizeOf :: PerformanceConfigurationINTEL -> Int
$csizeOf :: PerformanceConfigurationINTEL -> Int
Storable, PerformanceConfigurationINTEL
forall a. a -> Zero a
zero :: PerformanceConfigurationINTEL
$czero :: PerformanceConfigurationINTEL
Zero)
deriving anyclass (Eq PerformanceConfigurationINTEL
Zero PerformanceConfigurationINTEL
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType PerformanceConfigurationINTEL where
objectTypeAndHandle :: PerformanceConfigurationINTEL -> (ObjectType, Word64)
objectTypeAndHandle (PerformanceConfigurationINTEL Word64
h) = ( ObjectType
OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL
, Word64
h )
instance Show PerformanceConfigurationINTEL where
showsPrec :: Int -> PerformanceConfigurationINTEL -> ShowS
showsPrec Int
p (PerformanceConfigurationINTEL Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"PerformanceConfigurationINTEL 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype BufferCollectionFUCHSIA = BufferCollectionFUCHSIA Word64
deriving newtype (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c/= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
== :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c== :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
Eq, Eq BufferCollectionFUCHSIA
BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
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 :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
$cmin :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
max :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
$cmax :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
>= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c>= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
> :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c> :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
<= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c<= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
< :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c< :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
compare :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
$ccompare :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
Ord, Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
Ptr BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
BufferCollectionFUCHSIA -> Int
forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> 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 BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
$cpoke :: Ptr BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
peek :: Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
$cpeek :: Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
pokeByteOff :: forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
pokeElemOff :: Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
$cpokeElemOff :: Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
peekElemOff :: Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
$cpeekElemOff :: Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
alignment :: BufferCollectionFUCHSIA -> Int
$calignment :: BufferCollectionFUCHSIA -> Int
sizeOf :: BufferCollectionFUCHSIA -> Int
$csizeOf :: BufferCollectionFUCHSIA -> Int
Storable, BufferCollectionFUCHSIA
forall a. a -> Zero a
zero :: BufferCollectionFUCHSIA
$czero :: BufferCollectionFUCHSIA
Zero)
deriving anyclass (Eq BufferCollectionFUCHSIA
Zero BufferCollectionFUCHSIA
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType BufferCollectionFUCHSIA where
objectTypeAndHandle :: BufferCollectionFUCHSIA -> (ObjectType, Word64)
objectTypeAndHandle (BufferCollectionFUCHSIA Word64
h) = ( ObjectType
OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA
, Word64
h )
instance Show BufferCollectionFUCHSIA where
showsPrec :: Int -> BufferCollectionFUCHSIA -> ShowS
showsPrec Int
p (BufferCollectionFUCHSIA Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"BufferCollectionFUCHSIA 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype DeferredOperationKHR = DeferredOperationKHR Word64
deriving newtype (DeferredOperationKHR -> DeferredOperationKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
== :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c== :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
Eq, Eq DeferredOperationKHR
DeferredOperationKHR -> DeferredOperationKHR -> Bool
DeferredOperationKHR -> DeferredOperationKHR -> Ordering
DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
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 :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
$cmin :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
max :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
$cmax :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
>= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c>= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
> :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c> :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
<= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c<= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
< :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c< :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
compare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
$ccompare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
Ord, Ptr DeferredOperationKHR -> IO DeferredOperationKHR
Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
DeferredOperationKHR -> Int
forall b. Ptr b -> Int -> IO DeferredOperationKHR
forall b. Ptr b -> Int -> DeferredOperationKHR -> 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 DeferredOperationKHR -> DeferredOperationKHR -> IO ()
$cpoke :: Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
peek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
$cpeek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
pokeByteOff :: forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DeferredOperationKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeferredOperationKHR
pokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
$cpokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
peekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
$cpeekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
alignment :: DeferredOperationKHR -> Int
$calignment :: DeferredOperationKHR -> Int
sizeOf :: DeferredOperationKHR -> Int
$csizeOf :: DeferredOperationKHR -> Int
Storable, DeferredOperationKHR
forall a. a -> Zero a
zero :: DeferredOperationKHR
$czero :: DeferredOperationKHR
Zero)
deriving anyclass (Eq DeferredOperationKHR
Zero DeferredOperationKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DeferredOperationKHR where
objectTypeAndHandle :: DeferredOperationKHR -> (ObjectType, Word64)
objectTypeAndHandle (DeferredOperationKHR Word64
h) = ( ObjectType
OBJECT_TYPE_DEFERRED_OPERATION_KHR
, Word64
h )
instance Show DeferredOperationKHR where
showsPrec :: Int -> DeferredOperationKHR -> ShowS
showsPrec Int
p (DeferredOperationKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DeferredOperationKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype CuModuleNVX = CuModuleNVX Word64
deriving newtype (CuModuleNVX -> CuModuleNVX -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CuModuleNVX -> CuModuleNVX -> Bool
$c/= :: CuModuleNVX -> CuModuleNVX -> Bool
== :: CuModuleNVX -> CuModuleNVX -> Bool
$c== :: CuModuleNVX -> CuModuleNVX -> Bool
Eq, Eq CuModuleNVX
CuModuleNVX -> CuModuleNVX -> Bool
CuModuleNVX -> CuModuleNVX -> Ordering
CuModuleNVX -> CuModuleNVX -> CuModuleNVX
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 :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
$cmin :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
max :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
$cmax :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
>= :: CuModuleNVX -> CuModuleNVX -> Bool
$c>= :: CuModuleNVX -> CuModuleNVX -> Bool
> :: CuModuleNVX -> CuModuleNVX -> Bool
$c> :: CuModuleNVX -> CuModuleNVX -> Bool
<= :: CuModuleNVX -> CuModuleNVX -> Bool
$c<= :: CuModuleNVX -> CuModuleNVX -> Bool
< :: CuModuleNVX -> CuModuleNVX -> Bool
$c< :: CuModuleNVX -> CuModuleNVX -> Bool
compare :: CuModuleNVX -> CuModuleNVX -> Ordering
$ccompare :: CuModuleNVX -> CuModuleNVX -> Ordering
Ord, Ptr CuModuleNVX -> IO CuModuleNVX
Ptr CuModuleNVX -> Int -> IO CuModuleNVX
Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
Ptr CuModuleNVX -> CuModuleNVX -> IO ()
CuModuleNVX -> Int
forall b. Ptr b -> Int -> IO CuModuleNVX
forall b. Ptr b -> Int -> CuModuleNVX -> 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 CuModuleNVX -> CuModuleNVX -> IO ()
$cpoke :: Ptr CuModuleNVX -> CuModuleNVX -> IO ()
peek :: Ptr CuModuleNVX -> IO CuModuleNVX
$cpeek :: Ptr CuModuleNVX -> IO CuModuleNVX
pokeByteOff :: forall b. Ptr b -> Int -> CuModuleNVX -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CuModuleNVX -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO CuModuleNVX
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CuModuleNVX
pokeElemOff :: Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
$cpokeElemOff :: Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
peekElemOff :: Ptr CuModuleNVX -> Int -> IO CuModuleNVX
$cpeekElemOff :: Ptr CuModuleNVX -> Int -> IO CuModuleNVX
alignment :: CuModuleNVX -> Int
$calignment :: CuModuleNVX -> Int
sizeOf :: CuModuleNVX -> Int
$csizeOf :: CuModuleNVX -> Int
Storable, CuModuleNVX
forall a. a -> Zero a
zero :: CuModuleNVX
$czero :: CuModuleNVX
Zero)
deriving anyclass (Eq CuModuleNVX
Zero CuModuleNVX
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType CuModuleNVX where
objectTypeAndHandle :: CuModuleNVX -> (ObjectType, Word64)
objectTypeAndHandle (CuModuleNVX Word64
h) = (ObjectType
OBJECT_TYPE_CU_MODULE_NVX, Word64
h)
instance Show CuModuleNVX where
showsPrec :: Int -> CuModuleNVX -> ShowS
showsPrec Int
p (CuModuleNVX Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CuModuleNVX 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype CuFunctionNVX = CuFunctionNVX Word64
deriving newtype (CuFunctionNVX -> CuFunctionNVX -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c/= :: CuFunctionNVX -> CuFunctionNVX -> Bool
== :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c== :: CuFunctionNVX -> CuFunctionNVX -> Bool
Eq, Eq CuFunctionNVX
CuFunctionNVX -> CuFunctionNVX -> Bool
CuFunctionNVX -> CuFunctionNVX -> Ordering
CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
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 :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
$cmin :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
max :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
$cmax :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
>= :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c>= :: CuFunctionNVX -> CuFunctionNVX -> Bool
> :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c> :: CuFunctionNVX -> CuFunctionNVX -> Bool
<= :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c<= :: CuFunctionNVX -> CuFunctionNVX -> Bool
< :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c< :: CuFunctionNVX -> CuFunctionNVX -> Bool
compare :: CuFunctionNVX -> CuFunctionNVX -> Ordering
$ccompare :: CuFunctionNVX -> CuFunctionNVX -> Ordering
Ord, Ptr CuFunctionNVX -> IO CuFunctionNVX
Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
Ptr CuFunctionNVX -> CuFunctionNVX -> IO ()
CuFunctionNVX -> Int
forall b. Ptr b -> Int -> IO CuFunctionNVX
forall b. Ptr b -> Int -> CuFunctionNVX -> 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 CuFunctionNVX -> CuFunctionNVX -> IO ()
$cpoke :: Ptr CuFunctionNVX -> CuFunctionNVX -> IO ()
peek :: Ptr CuFunctionNVX -> IO CuFunctionNVX
$cpeek :: Ptr CuFunctionNVX -> IO CuFunctionNVX
pokeByteOff :: forall b. Ptr b -> Int -> CuFunctionNVX -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CuFunctionNVX -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO CuFunctionNVX
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CuFunctionNVX
pokeElemOff :: Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
$cpokeElemOff :: Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
peekElemOff :: Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
$cpeekElemOff :: Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
alignment :: CuFunctionNVX -> Int
$calignment :: CuFunctionNVX -> Int
sizeOf :: CuFunctionNVX -> Int
$csizeOf :: CuFunctionNVX -> Int
Storable, CuFunctionNVX
forall a. a -> Zero a
zero :: CuFunctionNVX
$czero :: CuFunctionNVX
Zero)
deriving anyclass (Eq CuFunctionNVX
Zero CuFunctionNVX
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType CuFunctionNVX where
objectTypeAndHandle :: CuFunctionNVX -> (ObjectType, Word64)
objectTypeAndHandle (CuFunctionNVX Word64
h) = (ObjectType
OBJECT_TYPE_CU_FUNCTION_NVX, Word64
h)
instance Show CuFunctionNVX where
showsPrec :: Int -> CuFunctionNVX -> ShowS
showsPrec Int
p (CuFunctionNVX Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CuFunctionNVX 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype OpticalFlowSessionNV = OpticalFlowSessionNV Word64
deriving newtype (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c/= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
== :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c== :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
Eq, Eq OpticalFlowSessionNV
OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
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 :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
$cmin :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
max :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
$cmax :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
>= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c>= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
> :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c> :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
<= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c<= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
< :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c< :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
compare :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
$ccompare :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
Ord, Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
OpticalFlowSessionNV -> Int
forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
forall b. Ptr b -> Int -> OpticalFlowSessionNV -> 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 OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
$cpoke :: Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
peek :: Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
$cpeek :: Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
pokeByteOff :: forall b. Ptr b -> Int -> OpticalFlowSessionNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OpticalFlowSessionNV -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
pokeElemOff :: Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
$cpokeElemOff :: Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
peekElemOff :: Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
$cpeekElemOff :: Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
alignment :: OpticalFlowSessionNV -> Int
$calignment :: OpticalFlowSessionNV -> Int
sizeOf :: OpticalFlowSessionNV -> Int
$csizeOf :: OpticalFlowSessionNV -> Int
Storable, OpticalFlowSessionNV
forall a. a -> Zero a
zero :: OpticalFlowSessionNV
$czero :: OpticalFlowSessionNV
Zero)
deriving anyclass (Eq OpticalFlowSessionNV
Zero OpticalFlowSessionNV
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType OpticalFlowSessionNV where
objectTypeAndHandle :: OpticalFlowSessionNV -> (ObjectType, Word64)
objectTypeAndHandle (OpticalFlowSessionNV Word64
h) = ( ObjectType
OBJECT_TYPE_OPTICAL_FLOW_SESSION_NV
, Word64
h )
instance Show OpticalFlowSessionNV where
showsPrec :: Int -> OpticalFlowSessionNV -> ShowS
showsPrec Int
p (OpticalFlowSessionNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"OpticalFlowSessionNV 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype MicromapEXT = MicromapEXT Word64
deriving newtype (MicromapEXT -> MicromapEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapEXT -> MicromapEXT -> Bool
$c/= :: MicromapEXT -> MicromapEXT -> Bool
== :: MicromapEXT -> MicromapEXT -> Bool
$c== :: MicromapEXT -> MicromapEXT -> Bool
Eq, Eq MicromapEXT
MicromapEXT -> MicromapEXT -> Bool
MicromapEXT -> MicromapEXT -> Ordering
MicromapEXT -> MicromapEXT -> MicromapEXT
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 :: MicromapEXT -> MicromapEXT -> MicromapEXT
$cmin :: MicromapEXT -> MicromapEXT -> MicromapEXT
max :: MicromapEXT -> MicromapEXT -> MicromapEXT
$cmax :: MicromapEXT -> MicromapEXT -> MicromapEXT
>= :: MicromapEXT -> MicromapEXT -> Bool
$c>= :: MicromapEXT -> MicromapEXT -> Bool
> :: MicromapEXT -> MicromapEXT -> Bool
$c> :: MicromapEXT -> MicromapEXT -> Bool
<= :: MicromapEXT -> MicromapEXT -> Bool
$c<= :: MicromapEXT -> MicromapEXT -> Bool
< :: MicromapEXT -> MicromapEXT -> Bool
$c< :: MicromapEXT -> MicromapEXT -> Bool
compare :: MicromapEXT -> MicromapEXT -> Ordering
$ccompare :: MicromapEXT -> MicromapEXT -> Ordering
Ord, Ptr MicromapEXT -> IO MicromapEXT
Ptr MicromapEXT -> Int -> IO MicromapEXT
Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
Ptr MicromapEXT -> MicromapEXT -> IO ()
MicromapEXT -> Int
forall b. Ptr b -> Int -> IO MicromapEXT
forall b. Ptr b -> Int -> MicromapEXT -> 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 MicromapEXT -> MicromapEXT -> IO ()
$cpoke :: Ptr MicromapEXT -> MicromapEXT -> IO ()
peek :: Ptr MicromapEXT -> IO MicromapEXT
$cpeek :: Ptr MicromapEXT -> IO MicromapEXT
pokeByteOff :: forall b. Ptr b -> Int -> MicromapEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MicromapEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MicromapEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MicromapEXT
pokeElemOff :: Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
$cpokeElemOff :: Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
peekElemOff :: Ptr MicromapEXT -> Int -> IO MicromapEXT
$cpeekElemOff :: Ptr MicromapEXT -> Int -> IO MicromapEXT
alignment :: MicromapEXT -> Int
$calignment :: MicromapEXT -> Int
sizeOf :: MicromapEXT -> Int
$csizeOf :: MicromapEXT -> Int
Storable, MicromapEXT
forall a. a -> Zero a
zero :: MicromapEXT
$czero :: MicromapEXT
Zero)
deriving anyclass (Eq MicromapEXT
Zero MicromapEXT
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType MicromapEXT where
objectTypeAndHandle :: MicromapEXT -> (ObjectType, Word64)
objectTypeAndHandle (MicromapEXT Word64
h) = (ObjectType
OBJECT_TYPE_MICROMAP_EXT, Word64
h)
instance Show MicromapEXT where
showsPrec :: Int -> MicromapEXT -> ShowS
showsPrec Int
p (MicromapEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"MicromapEXT 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype ShaderEXT = ShaderEXT Word64
deriving newtype (ShaderEXT -> ShaderEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShaderEXT -> ShaderEXT -> Bool
$c/= :: ShaderEXT -> ShaderEXT -> Bool
== :: ShaderEXT -> ShaderEXT -> Bool
$c== :: ShaderEXT -> ShaderEXT -> Bool
Eq, Eq ShaderEXT
ShaderEXT -> ShaderEXT -> Bool
ShaderEXT -> ShaderEXT -> Ordering
ShaderEXT -> ShaderEXT -> ShaderEXT
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 :: ShaderEXT -> ShaderEXT -> ShaderEXT
$cmin :: ShaderEXT -> ShaderEXT -> ShaderEXT
max :: ShaderEXT -> ShaderEXT -> ShaderEXT
$cmax :: ShaderEXT -> ShaderEXT -> ShaderEXT
>= :: ShaderEXT -> ShaderEXT -> Bool
$c>= :: ShaderEXT -> ShaderEXT -> Bool
> :: ShaderEXT -> ShaderEXT -> Bool
$c> :: ShaderEXT -> ShaderEXT -> Bool
<= :: ShaderEXT -> ShaderEXT -> Bool
$c<= :: ShaderEXT -> ShaderEXT -> Bool
< :: ShaderEXT -> ShaderEXT -> Bool
$c< :: ShaderEXT -> ShaderEXT -> Bool
compare :: ShaderEXT -> ShaderEXT -> Ordering
$ccompare :: ShaderEXT -> ShaderEXT -> Ordering
Ord, Ptr ShaderEXT -> IO ShaderEXT
Ptr ShaderEXT -> Int -> IO ShaderEXT
Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
Ptr ShaderEXT -> ShaderEXT -> IO ()
ShaderEXT -> Int
forall b. Ptr b -> Int -> IO ShaderEXT
forall b. Ptr b -> Int -> ShaderEXT -> 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 ShaderEXT -> ShaderEXT -> IO ()
$cpoke :: Ptr ShaderEXT -> ShaderEXT -> IO ()
peek :: Ptr ShaderEXT -> IO ShaderEXT
$cpeek :: Ptr ShaderEXT -> IO ShaderEXT
pokeByteOff :: forall b. Ptr b -> Int -> ShaderEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ShaderEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO ShaderEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ShaderEXT
pokeElemOff :: Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
$cpokeElemOff :: Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
peekElemOff :: Ptr ShaderEXT -> Int -> IO ShaderEXT
$cpeekElemOff :: Ptr ShaderEXT -> Int -> IO ShaderEXT
alignment :: ShaderEXT -> Int
$calignment :: ShaderEXT -> Int
sizeOf :: ShaderEXT -> Int
$csizeOf :: ShaderEXT -> Int
Storable, ShaderEXT
forall a. a -> Zero a
zero :: ShaderEXT
$czero :: ShaderEXT
Zero)
deriving anyclass (Eq ShaderEXT
Zero ShaderEXT
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType ShaderEXT where
objectTypeAndHandle :: ShaderEXT -> (ObjectType, Word64)
objectTypeAndHandle (ShaderEXT Word64
h) = (ObjectType
OBJECT_TYPE_SHADER_EXT, Word64
h)
instance Show ShaderEXT where
showsPrec :: Int -> ShaderEXT -> ShowS
showsPrec Int
p (ShaderEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"ShaderEXT 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype DisplayKHR = DisplayKHR Word64
deriving newtype (DisplayKHR -> DisplayKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayKHR -> DisplayKHR -> Bool
$c/= :: DisplayKHR -> DisplayKHR -> Bool
== :: DisplayKHR -> DisplayKHR -> Bool
$c== :: DisplayKHR -> DisplayKHR -> Bool
Eq, Eq DisplayKHR
DisplayKHR -> DisplayKHR -> Bool
DisplayKHR -> DisplayKHR -> Ordering
DisplayKHR -> DisplayKHR -> DisplayKHR
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 :: DisplayKHR -> DisplayKHR -> DisplayKHR
$cmin :: DisplayKHR -> DisplayKHR -> DisplayKHR
max :: DisplayKHR -> DisplayKHR -> DisplayKHR
$cmax :: DisplayKHR -> DisplayKHR -> DisplayKHR
>= :: DisplayKHR -> DisplayKHR -> Bool
$c>= :: DisplayKHR -> DisplayKHR -> Bool
> :: DisplayKHR -> DisplayKHR -> Bool
$c> :: DisplayKHR -> DisplayKHR -> Bool
<= :: DisplayKHR -> DisplayKHR -> Bool
$c<= :: DisplayKHR -> DisplayKHR -> Bool
< :: DisplayKHR -> DisplayKHR -> Bool
$c< :: DisplayKHR -> DisplayKHR -> Bool
compare :: DisplayKHR -> DisplayKHR -> Ordering
$ccompare :: DisplayKHR -> DisplayKHR -> Ordering
Ord, Ptr DisplayKHR -> IO DisplayKHR
Ptr DisplayKHR -> Int -> IO DisplayKHR
Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
Ptr DisplayKHR -> DisplayKHR -> IO ()
DisplayKHR -> Int
forall b. Ptr b -> Int -> IO DisplayKHR
forall b. Ptr b -> Int -> DisplayKHR -> 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 DisplayKHR -> DisplayKHR -> IO ()
$cpoke :: Ptr DisplayKHR -> DisplayKHR -> IO ()
peek :: Ptr DisplayKHR -> IO DisplayKHR
$cpeek :: Ptr DisplayKHR -> IO DisplayKHR
pokeByteOff :: forall b. Ptr b -> Int -> DisplayKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DisplayKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayKHR
pokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
$cpokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
peekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
$cpeekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
alignment :: DisplayKHR -> Int
$calignment :: DisplayKHR -> Int
sizeOf :: DisplayKHR -> Int
$csizeOf :: DisplayKHR -> Int
Storable, DisplayKHR
forall a. a -> Zero a
zero :: DisplayKHR
$czero :: DisplayKHR
Zero)
deriving anyclass (Eq DisplayKHR
Zero DisplayKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DisplayKHR where
objectTypeAndHandle :: DisplayKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayKHR Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_KHR, Word64
h)
instance Show DisplayKHR where
showsPrec :: Int -> DisplayKHR -> ShowS
showsPrec Int
p (DisplayKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DisplayKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype DisplayModeKHR = DisplayModeKHR Word64
deriving newtype (DisplayModeKHR -> DisplayModeKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
== :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c== :: DisplayModeKHR -> DisplayModeKHR -> Bool
Eq, Eq DisplayModeKHR
DisplayModeKHR -> DisplayModeKHR -> Bool
DisplayModeKHR -> DisplayModeKHR -> Ordering
DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
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 :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
$cmin :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
max :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
$cmax :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
>= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c>= :: DisplayModeKHR -> DisplayModeKHR -> Bool
> :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c> :: DisplayModeKHR -> DisplayModeKHR -> Bool
<= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c<= :: DisplayModeKHR -> DisplayModeKHR -> Bool
< :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c< :: DisplayModeKHR -> DisplayModeKHR -> Bool
compare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
$ccompare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
Ord, Ptr DisplayModeKHR -> IO DisplayModeKHR
Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
DisplayModeKHR -> Int
forall b. Ptr b -> Int -> IO DisplayModeKHR
forall b. Ptr b -> Int -> DisplayModeKHR -> 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 DisplayModeKHR -> DisplayModeKHR -> IO ()
$cpoke :: Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
peek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
$cpeek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
pokeByteOff :: forall b. Ptr b -> Int -> DisplayModeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayModeKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DisplayModeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayModeKHR
pokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
$cpokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
peekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
$cpeekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
alignment :: DisplayModeKHR -> Int
$calignment :: DisplayModeKHR -> Int
sizeOf :: DisplayModeKHR -> Int
$csizeOf :: DisplayModeKHR -> Int
Storable, DisplayModeKHR
forall a. a -> Zero a
zero :: DisplayModeKHR
$czero :: DisplayModeKHR
Zero)
deriving anyclass (Eq DisplayModeKHR
Zero DisplayModeKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DisplayModeKHR where
objectTypeAndHandle :: DisplayModeKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayModeKHR Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_MODE_KHR, Word64
h)
instance Show DisplayModeKHR where
showsPrec :: Int -> DisplayModeKHR -> ShowS
showsPrec Int
p (DisplayModeKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DisplayModeKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype SurfaceKHR = SurfaceKHR Word64
deriving newtype (SurfaceKHR -> SurfaceKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceKHR -> SurfaceKHR -> Bool
$c/= :: SurfaceKHR -> SurfaceKHR -> Bool
== :: SurfaceKHR -> SurfaceKHR -> Bool
$c== :: SurfaceKHR -> SurfaceKHR -> Bool
Eq, Eq SurfaceKHR
SurfaceKHR -> SurfaceKHR -> Bool
SurfaceKHR -> SurfaceKHR -> Ordering
SurfaceKHR -> SurfaceKHR -> SurfaceKHR
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 :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
$cmin :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
max :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
$cmax :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
>= :: SurfaceKHR -> SurfaceKHR -> Bool
$c>= :: SurfaceKHR -> SurfaceKHR -> Bool
> :: SurfaceKHR -> SurfaceKHR -> Bool
$c> :: SurfaceKHR -> SurfaceKHR -> Bool
<= :: SurfaceKHR -> SurfaceKHR -> Bool
$c<= :: SurfaceKHR -> SurfaceKHR -> Bool
< :: SurfaceKHR -> SurfaceKHR -> Bool
$c< :: SurfaceKHR -> SurfaceKHR -> Bool
compare :: SurfaceKHR -> SurfaceKHR -> Ordering
$ccompare :: SurfaceKHR -> SurfaceKHR -> Ordering
Ord, Ptr SurfaceKHR -> IO SurfaceKHR
Ptr SurfaceKHR -> Int -> IO SurfaceKHR
Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
Ptr SurfaceKHR -> SurfaceKHR -> IO ()
SurfaceKHR -> Int
forall b. Ptr b -> Int -> IO SurfaceKHR
forall b. Ptr b -> Int -> SurfaceKHR -> 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 SurfaceKHR -> SurfaceKHR -> IO ()
$cpoke :: Ptr SurfaceKHR -> SurfaceKHR -> IO ()
peek :: Ptr SurfaceKHR -> IO SurfaceKHR
$cpeek :: Ptr SurfaceKHR -> IO SurfaceKHR
pokeByteOff :: forall b. Ptr b -> Int -> SurfaceKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SurfaceKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO SurfaceKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SurfaceKHR
pokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
$cpokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
peekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
$cpeekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
alignment :: SurfaceKHR -> Int
$calignment :: SurfaceKHR -> Int
sizeOf :: SurfaceKHR -> Int
$csizeOf :: SurfaceKHR -> Int
Storable, SurfaceKHR
forall a. a -> Zero a
zero :: SurfaceKHR
$czero :: SurfaceKHR
Zero)
deriving anyclass (Eq SurfaceKHR
Zero SurfaceKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType SurfaceKHR where
objectTypeAndHandle :: SurfaceKHR -> (ObjectType, Word64)
objectTypeAndHandle (SurfaceKHR Word64
h) = (ObjectType
OBJECT_TYPE_SURFACE_KHR, Word64
h)
instance Show SurfaceKHR where
showsPrec :: Int -> SurfaceKHR -> ShowS
showsPrec Int
p (SurfaceKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"SurfaceKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype SwapchainKHR = SwapchainKHR Word64
deriving newtype (SwapchainKHR -> SwapchainKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapchainKHR -> SwapchainKHR -> Bool
$c/= :: SwapchainKHR -> SwapchainKHR -> Bool
== :: SwapchainKHR -> SwapchainKHR -> Bool
$c== :: SwapchainKHR -> SwapchainKHR -> Bool
Eq, Eq SwapchainKHR
SwapchainKHR -> SwapchainKHR -> Bool
SwapchainKHR -> SwapchainKHR -> Ordering
SwapchainKHR -> SwapchainKHR -> SwapchainKHR
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 :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
$cmin :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
max :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
$cmax :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
>= :: SwapchainKHR -> SwapchainKHR -> Bool
$c>= :: SwapchainKHR -> SwapchainKHR -> Bool
> :: SwapchainKHR -> SwapchainKHR -> Bool
$c> :: SwapchainKHR -> SwapchainKHR -> Bool
<= :: SwapchainKHR -> SwapchainKHR -> Bool
$c<= :: SwapchainKHR -> SwapchainKHR -> Bool
< :: SwapchainKHR -> SwapchainKHR -> Bool
$c< :: SwapchainKHR -> SwapchainKHR -> Bool
compare :: SwapchainKHR -> SwapchainKHR -> Ordering
$ccompare :: SwapchainKHR -> SwapchainKHR -> Ordering
Ord, Ptr SwapchainKHR -> IO SwapchainKHR
Ptr SwapchainKHR -> Int -> IO SwapchainKHR
Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
Ptr SwapchainKHR -> SwapchainKHR -> IO ()
SwapchainKHR -> Int
forall b. Ptr b -> Int -> IO SwapchainKHR
forall b. Ptr b -> Int -> SwapchainKHR -> 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 SwapchainKHR -> SwapchainKHR -> IO ()
$cpoke :: Ptr SwapchainKHR -> SwapchainKHR -> IO ()
peek :: Ptr SwapchainKHR -> IO SwapchainKHR
$cpeek :: Ptr SwapchainKHR -> IO SwapchainKHR
pokeByteOff :: forall b. Ptr b -> Int -> SwapchainKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SwapchainKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO SwapchainKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SwapchainKHR
pokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
$cpokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
peekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
$cpeekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
alignment :: SwapchainKHR -> Int
$calignment :: SwapchainKHR -> Int
sizeOf :: SwapchainKHR -> Int
$csizeOf :: SwapchainKHR -> Int
Storable, SwapchainKHR
forall a. a -> Zero a
zero :: SwapchainKHR
$czero :: SwapchainKHR
Zero)
deriving anyclass (Eq SwapchainKHR
Zero SwapchainKHR
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType SwapchainKHR where
objectTypeAndHandle :: SwapchainKHR -> (ObjectType, Word64)
objectTypeAndHandle (SwapchainKHR Word64
h) = (ObjectType
OBJECT_TYPE_SWAPCHAIN_KHR, Word64
h)
instance Show SwapchainKHR where
showsPrec :: Int -> SwapchainKHR -> ShowS
showsPrec Int
p (SwapchainKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"SwapchainKHR 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype DebugReportCallbackEXT = DebugReportCallbackEXT Word64
deriving newtype (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
== :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c== :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
Eq, Eq DebugReportCallbackEXT
DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
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 :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
$cmin :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
max :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
$cmax :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
>= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c>= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
> :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c> :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
<= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c<= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
< :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c< :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
compare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
$ccompare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
Ord, Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
DebugReportCallbackEXT -> Int
forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
forall b. Ptr b -> Int -> DebugReportCallbackEXT -> 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 DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
$cpoke :: Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
peek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
$cpeek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
pokeByteOff :: forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
pokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
$cpokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
peekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
$cpeekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
alignment :: DebugReportCallbackEXT -> Int
$calignment :: DebugReportCallbackEXT -> Int
sizeOf :: DebugReportCallbackEXT -> Int
$csizeOf :: DebugReportCallbackEXT -> Int
Storable, DebugReportCallbackEXT
forall a. a -> Zero a
zero :: DebugReportCallbackEXT
$czero :: DebugReportCallbackEXT
Zero)
deriving anyclass (Eq DebugReportCallbackEXT
Zero DebugReportCallbackEXT
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DebugReportCallbackEXT where
objectTypeAndHandle :: DebugReportCallbackEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugReportCallbackEXT Word64
h) = ( ObjectType
OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT
, Word64
h )
instance Show DebugReportCallbackEXT where
showsPrec :: Int -> DebugReportCallbackEXT -> ShowS
showsPrec Int
p (DebugReportCallbackEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DebugReportCallbackEXT 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)
newtype DebugUtilsMessengerEXT = DebugUtilsMessengerEXT Word64
deriving newtype (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
== :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c== :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
Eq, Eq DebugUtilsMessengerEXT
DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
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 :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
$cmin :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
max :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
$cmax :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
>= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c>= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
> :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c> :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
<= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c<= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
< :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c< :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
compare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
$ccompare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
Ord, Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
DebugUtilsMessengerEXT -> Int
forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> 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 DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
$cpoke :: Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
peek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
$cpeek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
pokeByteOff :: forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
pokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
$cpokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
peekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
$cpeekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
alignment :: DebugUtilsMessengerEXT -> Int
$calignment :: DebugUtilsMessengerEXT -> Int
sizeOf :: DebugUtilsMessengerEXT -> Int
$csizeOf :: DebugUtilsMessengerEXT -> Int
Storable, DebugUtilsMessengerEXT
forall a. a -> Zero a
zero :: DebugUtilsMessengerEXT
$czero :: DebugUtilsMessengerEXT
Zero)
deriving anyclass (Eq DebugUtilsMessengerEXT
Zero DebugUtilsMessengerEXT
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DebugUtilsMessengerEXT where
objectTypeAndHandle :: DebugUtilsMessengerEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugUtilsMessengerEXT Word64
h) = ( ObjectType
OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT
, Word64
h )
instance Show DebugUtilsMessengerEXT where
showsPrec :: Int -> DebugUtilsMessengerEXT -> ShowS
showsPrec Int
p (DebugUtilsMessengerEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DebugUtilsMessengerEXT 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)