{-# language CPP #-}
-- No documentation found for Chapter "Handles"
module Vulkan.Core11.Handles  ( DescriptorUpdateTemplate(..)
                              , SamplerYcbcrConversion(..)
                              , Instance(..)
                              , PhysicalDevice(..)
                              , Device(..)
                              , Queue(..)
                              , CommandBuffer(..)
                              , DeviceMemory(..)
                              , CommandPool(..)
                              , Buffer(..)
                              , Image(..)
                              , PipelineLayout(..)
                              , Sampler(..)
                              , DescriptorSet(..)
                              , DescriptorSetLayout(..)
                              ) 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_DESCRIPTOR_UPDATE_TEMPLATE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION))
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandPool(..))
import Vulkan.Core10.Handles (DescriptorSet(..))
import Vulkan.Core10.Handles (DescriptorSetLayout(..))
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (DeviceMemory(..))
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Sampler(..))
-- | VkDescriptorUpdateTemplate - Opaque handle to a descriptor update
-- template
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Extensions.VK_KHR_push_descriptor.cmdPushDescriptorSetWithTemplateKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.createDescriptorUpdateTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.createDescriptorUpdateTemplateKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.destroyDescriptorUpdateTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.destroyDescriptorUpdateTemplateKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplateKHR'
newtype DescriptorUpdateTemplate = DescriptorUpdateTemplate Word64
  deriving newtype (DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c/= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
== :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c== :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
Eq, Eq DescriptorUpdateTemplate
DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Ordering
DescriptorUpdateTemplate
-> DescriptorUpdateTemplate -> DescriptorUpdateTemplate
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 :: DescriptorUpdateTemplate
-> DescriptorUpdateTemplate -> DescriptorUpdateTemplate
$cmin :: DescriptorUpdateTemplate
-> DescriptorUpdateTemplate -> DescriptorUpdateTemplate
max :: DescriptorUpdateTemplate
-> DescriptorUpdateTemplate -> DescriptorUpdateTemplate
$cmax :: DescriptorUpdateTemplate
-> DescriptorUpdateTemplate -> DescriptorUpdateTemplate
>= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c>= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
> :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c> :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
<= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c<= :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
< :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
$c< :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Bool
compare :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Ordering
$ccompare :: DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> Ordering
Ord, Ptr DescriptorUpdateTemplate -> IO DescriptorUpdateTemplate
Ptr DescriptorUpdateTemplate -> Int -> IO DescriptorUpdateTemplate
Ptr DescriptorUpdateTemplate
-> Int -> DescriptorUpdateTemplate -> IO ()
Ptr DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> IO ()
DescriptorUpdateTemplate -> Int
forall b. Ptr b -> Int -> IO DescriptorUpdateTemplate
forall b. Ptr b -> Int -> DescriptorUpdateTemplate -> 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 DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> IO ()
$cpoke :: Ptr DescriptorUpdateTemplate -> DescriptorUpdateTemplate -> IO ()
peek :: Ptr DescriptorUpdateTemplate -> IO DescriptorUpdateTemplate
$cpeek :: Ptr DescriptorUpdateTemplate -> IO DescriptorUpdateTemplate
pokeByteOff :: forall b. Ptr b -> Int -> DescriptorUpdateTemplate -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DescriptorUpdateTemplate -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DescriptorUpdateTemplate
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DescriptorUpdateTemplate
pokeElemOff :: Ptr DescriptorUpdateTemplate
-> Int -> DescriptorUpdateTemplate -> IO ()
$cpokeElemOff :: Ptr DescriptorUpdateTemplate
-> Int -> DescriptorUpdateTemplate -> IO ()
peekElemOff :: Ptr DescriptorUpdateTemplate -> Int -> IO DescriptorUpdateTemplate
$cpeekElemOff :: Ptr DescriptorUpdateTemplate -> Int -> IO DescriptorUpdateTemplate
alignment :: DescriptorUpdateTemplate -> Int
$calignment :: DescriptorUpdateTemplate -> Int
sizeOf :: DescriptorUpdateTemplate -> Int
$csizeOf :: DescriptorUpdateTemplate -> Int
Storable, DescriptorUpdateTemplate
forall a. a -> Zero a
zero :: DescriptorUpdateTemplate
$czero :: DescriptorUpdateTemplate
Zero)
  deriving anyclass (Eq DescriptorUpdateTemplate
Zero DescriptorUpdateTemplate
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType DescriptorUpdateTemplate where
  objectTypeAndHandle :: DescriptorUpdateTemplate -> (ObjectType, Word64)
objectTypeAndHandle (DescriptorUpdateTemplate Word64
h) = ( ObjectType
OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE
                                                     , Word64
h )
instance Show DescriptorUpdateTemplate where
  showsPrec :: Int -> DescriptorUpdateTemplate -> ShowS
showsPrec Int
p (DescriptorUpdateTemplate Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DescriptorUpdateTemplate 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkSamplerYcbcrConversion - Opaque handle to a device-specific sampler
-- Y′CBCR conversion description
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.createSamplerYcbcrConversion',
-- 'Vulkan.Extensions.VK_KHR_sampler_ycbcr_conversion.createSamplerYcbcrConversionKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.destroySamplerYcbcrConversion',
-- 'Vulkan.Extensions.VK_KHR_sampler_ycbcr_conversion.destroySamplerYcbcrConversionKHR'
newtype SamplerYcbcrConversion = SamplerYcbcrConversion Word64
  deriving newtype (SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c/= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
== :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c== :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
Eq, Eq SamplerYcbcrConversion
SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
SamplerYcbcrConversion -> SamplerYcbcrConversion -> Ordering
SamplerYcbcrConversion
-> SamplerYcbcrConversion -> SamplerYcbcrConversion
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 :: SamplerYcbcrConversion
-> SamplerYcbcrConversion -> SamplerYcbcrConversion
$cmin :: SamplerYcbcrConversion
-> SamplerYcbcrConversion -> SamplerYcbcrConversion
max :: SamplerYcbcrConversion
-> SamplerYcbcrConversion -> SamplerYcbcrConversion
$cmax :: SamplerYcbcrConversion
-> SamplerYcbcrConversion -> SamplerYcbcrConversion
>= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c>= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
> :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c> :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
<= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c<= :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
< :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
$c< :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Bool
compare :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Ordering
$ccompare :: SamplerYcbcrConversion -> SamplerYcbcrConversion -> Ordering
Ord, Ptr SamplerYcbcrConversion -> IO SamplerYcbcrConversion
Ptr SamplerYcbcrConversion -> Int -> IO SamplerYcbcrConversion
Ptr SamplerYcbcrConversion
-> Int -> SamplerYcbcrConversion -> IO ()
Ptr SamplerYcbcrConversion -> SamplerYcbcrConversion -> IO ()
SamplerYcbcrConversion -> Int
forall b. Ptr b -> Int -> IO SamplerYcbcrConversion
forall b. Ptr b -> Int -> SamplerYcbcrConversion -> 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 SamplerYcbcrConversion -> SamplerYcbcrConversion -> IO ()
$cpoke :: Ptr SamplerYcbcrConversion -> SamplerYcbcrConversion -> IO ()
peek :: Ptr SamplerYcbcrConversion -> IO SamplerYcbcrConversion
$cpeek :: Ptr SamplerYcbcrConversion -> IO SamplerYcbcrConversion
pokeByteOff :: forall b. Ptr b -> Int -> SamplerYcbcrConversion -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SamplerYcbcrConversion -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO SamplerYcbcrConversion
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SamplerYcbcrConversion
pokeElemOff :: Ptr SamplerYcbcrConversion
-> Int -> SamplerYcbcrConversion -> IO ()
$cpokeElemOff :: Ptr SamplerYcbcrConversion
-> Int -> SamplerYcbcrConversion -> IO ()
peekElemOff :: Ptr SamplerYcbcrConversion -> Int -> IO SamplerYcbcrConversion
$cpeekElemOff :: Ptr SamplerYcbcrConversion -> Int -> IO SamplerYcbcrConversion
alignment :: SamplerYcbcrConversion -> Int
$calignment :: SamplerYcbcrConversion -> Int
sizeOf :: SamplerYcbcrConversion -> Int
$csizeOf :: SamplerYcbcrConversion -> Int
Storable, SamplerYcbcrConversion
forall a. a -> Zero a
zero :: SamplerYcbcrConversion
$czero :: SamplerYcbcrConversion
Zero)
  deriving anyclass (Eq SamplerYcbcrConversion
Zero SamplerYcbcrConversion
forall a. Eq a -> Zero a -> IsHandle a
IsHandle)
instance HasObjectType SamplerYcbcrConversion where
  objectTypeAndHandle :: SamplerYcbcrConversion -> (ObjectType, Word64)
objectTypeAndHandle (SamplerYcbcrConversion Word64
h) = ( ObjectType
OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION
                                                   , Word64
h )
instance Show SamplerYcbcrConversion where
  showsPrec :: Int -> SamplerYcbcrConversion -> ShowS
showsPrec Int
p (SamplerYcbcrConversion Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"SamplerYcbcrConversion 0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)