{-# 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 Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
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 Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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.Handles (Device(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.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.Exception (VulkanException(..))
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
getImageViewHandleNVX :: forall io
. (MonadIO io)
=>
Device
->
ImageViewHandleInfoNVX
-> io (Word32)
getImageViewHandleNVX :: forall (io :: * -> *).
MonadIO io =>
Device -> ImageViewHandleInfoNVX -> io Word32
getImageViewHandleNVX Device
device ImageViewHandleInfoNVX
info = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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 (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32)
vkGetImageViewHandleNVXPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetImageViewHandleNVX is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageViewHandleInfoNVX
info)
Word32
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetImageViewHandleNVX" (Ptr Device_T
-> ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO Word32
vkGetImageViewHandleNVX'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr ImageViewHandleInfoNVX
pInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
getImageViewAddressNVX :: forall io
. (MonadIO io)
=>
Device
->
ImageView
-> io (ImageViewAddressPropertiesNVX)
getImageViewAddressNVX :: forall (io :: * -> *).
MonadIO io =>
Device -> ImageView -> io ImageViewAddressPropertiesNVX
getImageViewAddressNVX Device
device ImageView
imageView = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ImageView
-> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO Result)
vkGetImageViewAddressNVXPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetImageViewAddressNVX is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @ImageViewAddressPropertiesNVX)
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetImageViewAddressNVX" (Ptr Device_T
-> ImageView
-> ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO Result
vkGetImageViewAddressNVX'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ImageView
imageView)
("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
pPProperties))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
ImageViewAddressPropertiesNVX
pProperties <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageViewAddressPropertiesNVX "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
pPProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (ImageViewAddressPropertiesNVX
pProperties)
data ImageViewHandleInfoNVX = ImageViewHandleInfoNVX
{
ImageViewHandleInfoNVX -> ImageView
imageView :: ImageView
,
ImageViewHandleInfoNVX -> DescriptorType
descriptorType :: DescriptorType
,
ImageViewHandleInfoNVX -> Sampler
sampler :: Sampler
}
deriving (Typeable, ImageViewHandleInfoNVX -> ImageViewHandleInfoNVX -> Bool
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 :: forall b.
ImageViewHandleInfoNVX
-> (("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b) -> IO b
withCStruct ImageViewHandleInfoNVX
x ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr ImageViewHandleInfoNVX
p -> 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 :: forall b.
("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> ImageViewHandleInfoNVX -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewHandleInfoNVX
p ImageViewHandleInfoNVX{Sampler
ImageView
DescriptorType
sampler :: Sampler
descriptorType :: DescriptorType
imageView :: ImageView
$sel:sampler:ImageViewHandleInfoNVX :: ImageViewHandleInfoNVX -> Sampler
$sel:descriptorType:ImageViewHandleInfoNVX :: ImageViewHandleInfoNVX -> DescriptorType
$sel:imageView:ImageViewHandleInfoNVX :: ImageViewHandleInfoNVX -> ImageView
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView)) (ImageView
imageView)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorType)) (DescriptorType
descriptorType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Sampler)) (Sampler
sampler)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. ("pInfo" ::: Ptr ImageViewHandleInfoNVX) -> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr ImageViewHandleInfoNVX
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorType)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewHandleInfoNVX where
peekCStruct :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> IO ImageViewHandleInfoNVX
peekCStruct "pInfo" ::: Ptr ImageViewHandleInfoNVX
p = do
ImageView
imageView <- forall a. Storable a => Ptr a -> IO a
peek @ImageView (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageView))
DescriptorType
descriptorType <- forall a. Storable a => Ptr a -> IO a
peek @DescriptorType (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DescriptorType))
Sampler
sampler <- forall a. Storable a => Ptr a -> IO a
peek @Sampler (("pInfo" ::: Ptr ImageViewHandleInfoNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Sampler))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
_ = Int
40
alignment :: ImageViewHandleInfoNVX -> Int
alignment ~ImageViewHandleInfoNVX
_ = Int
8
peek :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> IO ImageViewHandleInfoNVX
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr ImageViewHandleInfoNVX)
-> ImageViewHandleInfoNVX -> IO ()
poke "pInfo" ::: Ptr ImageViewHandleInfoNVX
ptr ImageViewHandleInfoNVX
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr ImageViewHandleInfoNVX
ptr ImageViewHandleInfoNVX
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewHandleInfoNVX where
zero :: ImageViewHandleInfoNVX
zero = ImageView -> DescriptorType -> Sampler -> ImageViewHandleInfoNVX
ImageViewHandleInfoNVX
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data ImageViewAddressPropertiesNVX = ImageViewAddressPropertiesNVX
{
ImageViewAddressPropertiesNVX -> DeviceAddress
deviceAddress :: DeviceAddress
,
ImageViewAddressPropertiesNVX -> DeviceAddress
size :: DeviceSize
}
deriving (Typeable, ImageViewAddressPropertiesNVX
-> ImageViewAddressPropertiesNVX -> Bool
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 :: forall b.
ImageViewAddressPropertiesNVX
-> (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b)
-> IO b
withCStruct ImageViewAddressPropertiesNVX
x ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p -> 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 :: forall b.
("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p ImageViewAddressPropertiesNVX{DeviceAddress
size :: DeviceAddress
deviceAddress :: DeviceAddress
$sel:size:ImageViewAddressPropertiesNVX :: ImageViewAddressPropertiesNVX -> DeviceAddress
$sel:deviceAddress:ImageViewAddressPropertiesNVX :: ImageViewAddressPropertiesNVX -> DeviceAddress
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (DeviceAddress
deviceAddress)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceAddress
size)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO b -> IO b
pokeZeroCStruct "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewAddressPropertiesNVX where
peekCStruct :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO ImageViewAddressPropertiesNVX
peekCStruct "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p = do
DeviceAddress
deviceAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceAddress))
DeviceAddress
size <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pProperties" ::: Ptr ImageViewAddressPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceAddress -> DeviceAddress -> ImageViewAddressPropertiesNVX
ImageViewAddressPropertiesNVX
DeviceAddress
deviceAddress DeviceAddress
size
instance Storable ImageViewAddressPropertiesNVX where
sizeOf :: ImageViewAddressPropertiesNVX -> Int
sizeOf ~ImageViewAddressPropertiesNVX
_ = Int
32
alignment :: ImageViewAddressPropertiesNVX -> Int
alignment ~ImageViewAddressPropertiesNVX
_ = Int
8
peek :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> IO ImageViewAddressPropertiesNVX
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pProperties" ::: Ptr ImageViewAddressPropertiesNVX)
-> ImageViewAddressPropertiesNVX -> IO ()
poke "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
ptr ImageViewAddressPropertiesNVX
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageViewAddressPropertiesNVX
ptr ImageViewAddressPropertiesNVX
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewAddressPropertiesNVX where
zero :: ImageViewAddressPropertiesNVX
zero = DeviceAddress -> DeviceAddress -> ImageViewAddressPropertiesNVX
ImageViewAddressPropertiesNVX
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION = 2
pattern NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: forall a. Integral a => a
$mNVX_IMAGE_VIEW_HANDLE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NVX_IMAGE_VIEW_HANDLE_SPEC_VERSION = 2
type NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME = "VK_NVX_image_view_handle"
pattern NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NVX_IMAGE_VIEW_HANDLE_EXTENSION_NAME = "VK_NVX_image_view_handle"