{-# language CPP #-}
module Vulkan.Extensions.VK_NVX_image_view_handle  ( getImageViewHandleNVX
                                                   , getImageViewAddressNVX
                                                   , ImageViewHandleInfoNVX(..)
                                                   , ImageViewAddressPropertiesNVX(..)
                                                   , NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION
                                                   , pattern NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION
                                                   , NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME
                                                   , pattern NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME
                                                   ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.Enums.DescriptorType (DescriptorType)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkGetImageViewAddressNVX))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageViewHandleNVX))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (ImageView)
import Vulkan.Core10.Handles (ImageView(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Sampler)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetImageViewHandleNVX
  :: FunPtr (Ptr Device_T -> Ptr ImageViewHandleInfoNVX -> IO Word32) -> Ptr Device_T -> Ptr ImageViewHandleInfoNVX -> IO Word32

-- | vkGetImageViewHandleNVX - Get the handle for an image view for a
-- specific descriptor type
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'ImageViewHandleInfoNVX'
getImageViewHandleNVX :: forall io
                       . (MonadIO io)
                      => -- | @device@ is the logical device that owns the image view.
                         --
                         -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                         Device
                      -> -- | @pInfo@ describes the image view to query and type of handle.
                         --
                         -- @pInfo@ /must/ be a valid pointer to a valid 'ImageViewHandleInfoNVX'
                         -- structure
                         ImageViewHandleInfoNVX
                      -> io (Word32)
getImageViewHandleNVX :: Device -> ImageViewHandleInfoNVX -> io Word32
getImageViewHandleNVX device :: Device
device info :: ImageViewHandleInfoNVX
info = IO Word32 -> io Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> io Word32)
-> (ContT Word32 IO Word32 -> IO Word32)
-> ContT Word32 IO Word32
-> io Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Word32 IO Word32 -> IO Word32
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Word32 IO Word32 -> io Word32)
-> ContT Word32 IO Word32 -> io Word32
forall a b. (a -> b) -> a -> b
$ do
  let vkGetImageViewHandleNVXPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
vkGetImageViewHandleNVXPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
pVkGetImageViewHandleNVX (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT Word32 IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Word32 IO ()) -> IO () -> ContT Word32 IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
vkGetImageViewHandleNVXPtr FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetImageViewHandleNVX is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetImageViewHandleNVX' :: Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32
vkGetImageViewHandleNVX' = FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
-> Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> IO Word32
mkVkGetImageViewHandleNVX FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
vkGetImageViewHandleNVXPtr
  "pInfo" ::: Ptr ImageViewHandleInfoNVX
pInfo <- ((("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
 -> IO Word32)
-> ContT Word32 IO ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
  -> IO Word32)
 -> ContT Word32 IO ("pInfo" ::: Ptr ImageViewHandleInfoNVX))
-> ((("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
    -> IO Word32)
-> ContT Word32 IO ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
forall a b. (a -> b) -> a -> b
$ ImageViewHandleInfoNVX
-> (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
-> IO Word32
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageViewHandleInfoNVX
info)
  Word32
r <- IO Word32 -> ContT Word32 IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32 -> ContT Word32 IO Word32)
-> IO Word32 -> ContT Word32 IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32
vkGetImageViewHandleNVX' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pInfo" ::: Ptr ImageViewHandleInfoNVX
pInfo
  Word32 -> ContT Word32 IO Word32
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word32 -> ContT Word32 IO Word32)
-> Word32 -> ContT Word32 IO Word32
forall a b. (a -> b) -> a -> b
$ (Word32
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetImageViewAddressNVX
  :: FunPtr (Ptr Device_T -> ImageView -> Ptr ImageViewAddressPropertiesNVX -> IO Result) -> Ptr Device_T -> ImageView -> Ptr ImageViewAddressPropertiesNVX -> IO Result

-- | vkGetImageViewAddressNVX - Get the device address of an image view
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_UNKNOWN'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.ImageView',
-- 'ImageViewAddressPropertiesNVX'
getImageViewAddressNVX :: forall io
                        . (MonadIO io)
                       => -- | @device@ is the logical device that owns the image view.
                          --
                          -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                          Device
                       -> -- | @imageView@ is a handle to the image view.
                          --
                          -- @imageView@ /must/ be a valid 'Vulkan.Core10.Handles.ImageView' handle
                          --
                          -- @imageView@ /must/ have been created, allocated, or retrieved from
                          -- @device@
                          ImageView
                       -> io (ImageViewAddressPropertiesNVX)
getImageViewAddressNVX :: Device -> ImageView -> io ImageViewAddressPropertiesNVX
getImageViewAddressNVX device :: Device
device imageView :: ImageView
imageView = IO ImageViewAddressPropertiesNVX
-> io ImageViewAddressPropertiesNVX
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageViewAddressPropertiesNVX
 -> io ImageViewAddressPropertiesNVX)
-> (ContT
      ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
    -> IO ImageViewAddressPropertiesNVX)
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
-> io ImageViewAddressPropertiesNVX
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
-> IO ImageViewAddressPropertiesNVX
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
 -> io ImageViewAddressPropertiesNVX)
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
-> io ImageViewAddressPropertiesNVX
forall a b. (a -> b) -> a -> b
$ do
  let vkGetImageViewAddressNVXPtr :: FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
vkGetImageViewAddressNVXPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ImageView
      -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
      -> IO Result)
pVkGetImageViewAddressNVX (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ImageViewAddressPropertiesNVX IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageViewAddressPropertiesNVX IO ())
-> IO () -> ContT ImageViewAddressPropertiesNVX IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
vkGetImageViewAddressNVXPtr FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ImageView
      -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetImageViewAddressNVX is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetImageViewAddressNVX' :: Ptr Device_T
-> ImageView
-> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO Result
vkGetImageViewAddressNVX' = FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
-> Ptr Device_T
-> ImageView
-> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO Result
mkVkGetImageViewAddressNVX FunPtr
  (Ptr Device_T
   -> ImageView
   -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
   -> IO Result)
vkGetImageViewAddressNVXPtr
  "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
pPProperties <- ((("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
  -> IO ImageViewAddressPropertiesNVX)
 -> IO ImageViewAddressPropertiesNVX)
-> ContT
     ImageViewAddressPropertiesNVX
     IO
     ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct ImageViewAddressPropertiesNVX =>
(("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @ImageViewAddressPropertiesNVX)
  Result
r <- IO Result -> ContT ImageViewAddressPropertiesNVX IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ImageViewAddressPropertiesNVX IO Result)
-> IO Result -> ContT ImageViewAddressPropertiesNVX IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ImageView
-> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO Result
vkGetImageViewAddressNVX' (Device -> Ptr Device_T
deviceHandle (Device
device)) (ImageView
imageView) ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
pPProperties)
  IO () -> ContT ImageViewAddressPropertiesNVX IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageViewAddressPropertiesNVX IO ())
-> IO () -> ContT ImageViewAddressPropertiesNVX IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  ImageViewAddressPropertiesNVX
pProperties <- IO ImageViewAddressPropertiesNVX
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ImageViewAddressPropertiesNVX
 -> ContT
      ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX)
-> IO ImageViewAddressPropertiesNVX
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO ImageViewAddressPropertiesNVX
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageViewAddressPropertiesNVX "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
pPProperties
  ImageViewAddressPropertiesNVX
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewAddressPropertiesNVX
 -> ContT
      ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX
-> ContT
     ImageViewAddressPropertiesNVX IO ImageViewAddressPropertiesNVX
forall a b. (a -> b) -> a -> b
$ (ImageViewAddressPropertiesNVX
pProperties)


-- | VkImageViewHandleInfoNVX - Structure specifying the image view for
-- handle queries
--
-- == Valid Usage
--
-- -   @descriptorType@ /must/ be
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE',
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE',
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER'
--
-- -   @sampler@ /must/ be a valid 'Vulkan.Core10.Handles.Sampler' if
--     @descriptorType@ is
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER'
--
-- -   If descriptorType is
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
--     the image that @imageView@ was created from /must/ have been created
--     with the
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT'
--     usage bit set
--
-- -   If descriptorType is
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE',
--     the image that @imageView@ was created from /must/ have been created
--     with the
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_STORAGE_BIT'
--     usage bit set
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @imageView@ /must/ be a valid 'Vulkan.Core10.Handles.ImageView'
--     handle
--
-- -   @descriptorType@ /must/ be a valid
--     'Vulkan.Core10.Enums.DescriptorType.DescriptorType' value
--
-- -   If @sampler@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @sampler@ /must/ be a valid 'Vulkan.Core10.Handles.Sampler' handle
--
-- -   Both of @imageView@, and @sampler@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.DescriptorType.DescriptorType',
-- 'Vulkan.Core10.Handles.ImageView', 'Vulkan.Core10.Handles.Sampler',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getImageViewHandleNVX'
data ImageViewHandleInfoNVX = ImageViewHandleInfoNVX
  { -- | @imageView@ is the image view to query.
    ImageViewHandleInfoNVX -> ImageView
imageView :: ImageView
  , -- | @descriptorType@ is the type of descriptor for which to query a handle.
    ImageViewHandleInfoNVX -> DescriptorType
descriptorType :: DescriptorType
  , -- | @sampler@ is the sampler to combine with the image view when generating
    -- the handle.
    ImageViewHandleInfoNVX -> Sampler
sampler :: Sampler
  }
  deriving (Typeable, ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
(ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool)
-> (ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool)
-> Eq ImageViewHandleInfoNVX
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
$c/= :: ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
== :: ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
$c== :: ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewHandleInfoNVX)
#endif
deriving instance Show ImageViewHandleInfoNVX

instance ToCStruct ImageViewHandleInfoNVX where
  withCStruct :: ImageViewHandleInfoNVX
-> (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b) -> IO b
withCStruct x :: ImageViewHandleInfoNVX
x f :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b
f = Int
-> Int
-> (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b) -> IO b)
-> (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pInfo" ::: Ptr ImageViewHandleInfoNVX
p -> ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> ImageViewHandleInfoNVX -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewHandleInfoNVX
p ImageViewHandleInfoNVX
x (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b
f "pInfo" ::: Ptr ImageViewHandleInfoNVX
p)
  pokeCStruct :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> ImageViewHandleInfoNVX -> IO b -> IO b
pokeCStruct p :: "pInfo" ::: Ptr ImageViewHandleInfoNVX
p ImageViewHandleInfoNVX{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ImageView -> ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr ImageView
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageView)) (ImageView
imageView)
    Ptr DescriptorType -> DescriptorType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> Int -> Ptr DescriptorType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DescriptorType)) (DescriptorType
descriptorType)
    Ptr Sampler -> Sampler -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr Sampler
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Sampler)) (Sampler
sampler)
    IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b -> IO b
pokeZeroCStruct p :: "pInfo" ::: Ptr ImageViewHandleInfoNVX
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ImageView -> ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr ImageView
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageView)) (ImageView
forall a. Zero a => a
zero)
    Ptr DescriptorType -> DescriptorType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> Int -> Ptr DescriptorType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DescriptorType)) (DescriptorType
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageViewHandleInfoNVX where
  peekCStruct :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> IO ImageViewHandleInfoNVX
peekCStruct p :: "pInfo" ::: Ptr ImageViewHandleInfoNVX
p = do
    ImageView
imageView <- Ptr ImageView -> IO ImageView
forall a. Storable a => Ptr a -> IO a
peek @ImageView (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr ImageView
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageView))
    DescriptorType
descriptorType <- Ptr DescriptorType -> IO DescriptorType
forall a. Storable a => Ptr a -> IO a
peek @DescriptorType (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> Int -> Ptr DescriptorType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DescriptorType))
    Sampler
sampler <- Ptr Sampler -> IO Sampler
forall a. Storable a => Ptr a -> IO a
peek @Sampler (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> Int -> Ptr Sampler
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Sampler))
    ImageViewHandleInfoNVX -> IO ImageViewHandleInfoNVX
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewHandleInfoNVX -> IO ImageViewHandleInfoNVX)
-> ImageViewHandleInfoNVX -> IO ImageViewHandleInfoNVX
forall a b. (a -> b) -> a -> b
$ ImageView -> DescriptorType -> Sampler -> ImageViewHandleInfoNVX
ImageViewHandleInfoNVX
             ImageView
imageView DescriptorType
descriptorType Sampler
sampler

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

instance Zero ImageViewHandleInfoNVX where
  zero :: ImageViewHandleInfoNVX
zero = ImageView -> DescriptorType -> Sampler -> ImageViewHandleInfoNVX
ImageViewHandleInfoNVX
           ImageView
forall a. Zero a => a
zero
           DescriptorType
forall a. Zero a => a
zero
           Sampler
forall a. Zero a => a
zero


-- | VkImageViewAddressPropertiesNVX - Structure specifying the image view
-- for handle queries
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceAddress',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getImageViewAddressNVX'
data ImageViewAddressPropertiesNVX = ImageViewAddressPropertiesNVX
  { -- | @deviceAddress@ is the device address of the image view.
    ImageViewAddressPropertiesNVX -> DeviceAddress
deviceAddress :: DeviceAddress
  , -- | @size@ is the size in bytes of the image view device memory.
    ImageViewAddressPropertiesNVX -> DeviceAddress
size :: DeviceSize
  }
  deriving (Typeable, ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
(ImageViewAddressPropertiesNVX
 -> ImageViewAddressPropertiesNVX -> Bool)
-> (ImageViewAddressPropertiesNVX
    -> ImageViewAddressPropertiesNVX -> Bool)
-> Eq ImageViewAddressPropertiesNVX
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
$c/= :: ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
== :: ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
$c== :: ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewAddressPropertiesNVX)
#endif
deriving instance Show ImageViewAddressPropertiesNVX

instance ToCStruct ImageViewAddressPropertiesNVX where
  withCStruct :: ImageViewAddressPropertiesNVX
-> (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
-> IO b
withCStruct x :: ImageViewAddressPropertiesNVX
x f :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
 -> IO b)
-> (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p -> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ImageViewAddressPropertiesNVX
x (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b
f "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p)
  pokeCStruct :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ImageViewAddressPropertiesNVX{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceAddress)) (DeviceAddress
deviceAddress)
    Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceAddress
size)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceAddress)) (DeviceAddress
forall a. Zero a => a
zero)
    Ptr DeviceAddress -> DeviceAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceAddress
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageViewAddressPropertiesNVX where
  peekCStruct :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO ImageViewAddressPropertiesNVX
peekCStruct p :: "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p = do
    DeviceAddress
deviceAddress <- Ptr DeviceAddress -> IO DeviceAddress
forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceAddress))
    DeviceAddress
size <- Ptr DeviceAddress -> IO DeviceAddress
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> Int -> Ptr DeviceAddress
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
    ImageViewAddressPropertiesNVX -> IO ImageViewAddressPropertiesNVX
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewAddressPropertiesNVX -> IO ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX
-> IO ImageViewAddressPropertiesNVX
forall a b. (a -> b) -> a -> b
$ DeviceAddress -> DeviceAddress -> ImageViewAddressPropertiesNVX
ImageViewAddressPropertiesNVX
             DeviceAddress
deviceAddress DeviceAddress
size

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

instance Zero ImageViewAddressPropertiesNVX where
  zero :: ImageViewAddressPropertiesNVX
zero = DeviceAddress -> DeviceAddress -> ImageViewAddressPropertiesNVX
ImageViewAddressPropertiesNVX
           DeviceAddress
forall a. Zero a => a
zero
           DeviceAddress
forall a. Zero a => a
zero


type NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION"
pattern NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: a
$mNVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION = 2


type NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME = "VK_NVX_image_view_handle"

-- No documentation found for TopLevel "VK_NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME"
pattern NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: a
$mNVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME = "VK_NVX_image_view_handle"