{-# language CPP #-} -- No documentation found for Chapter "ImageView" module Vulkan.Core10.ImageView ( createImageView , withImageView , destroyImageView , ComponentMapping(..) , ImageSubresourceRange(..) , ImageViewCreateInfo(..) , ImageView(..) , ImageViewType(..) , ComponentSwizzle(..) , ImageViewCreateFlagBits(..) , ImageViewCreateFlags ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Data.Typeable (eqT) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import GHC.Base (when) import GHC.IO (throwIO) import GHC.Ptr (castPtr) 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.Type.Equality ((:~:)(Refl)) 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.CStruct.Extends (forgetExtensions) import Vulkan.NamedType ((:::)) import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks) import Vulkan.CStruct.Extends (Chain) import Vulkan.Core10.Enums.ComponentSwizzle (ComponentSwizzle) import Vulkan.Core10.Handles (Device) import Vulkan.Core10.Handles (Device(..)) import Vulkan.Core10.Handles (Device(Device)) import Vulkan.Dynamic (DeviceCmds(pVkCreateImageView)) import Vulkan.Dynamic (DeviceCmds(pVkDestroyImageView)) import Vulkan.Core10.Handles (Device_T) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_metal_objects (ExportMetalObjectCreateInfoEXT) import Vulkan.CStruct.Extends (Extends) import Vulkan.CStruct.Extends (Extendss) import Vulkan.CStruct.Extends (Extensible(..)) import Vulkan.Core10.Enums.Format (Format) import Vulkan.Core10.Handles (Image) import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags) import Vulkan.Core10.Handles (ImageView) import Vulkan.Core10.Handles (ImageView(..)) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_astc_decode_mode (ImageViewASTCDecodeModeEXT) import Vulkan.Core10.Enums.ImageViewCreateFlagBits (ImageViewCreateFlags) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_view_min_lod (ImageViewMinLodCreateInfoEXT) import {-# SOURCE #-} Vulkan.Extensions.VK_QCOM_image_processing (ImageViewSampleWeightCreateInfoQCOM) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_sliced_view_of_3d (ImageViewSlicedCreateInfoEXT) import Vulkan.Core10.Enums.ImageViewType (ImageViewType) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (ImageViewUsageCreateInfo) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_descriptor_buffer (OpaqueCaptureDescriptorDataCreateInfoEXT) import Vulkan.CStruct.Extends (PeekChain) import Vulkan.CStruct.Extends (PeekChain(..)) import Vulkan.CStruct.Extends (PokeChain) import Vulkan.CStruct.Extends (PokeChain(..)) import Vulkan.Core10.Enums.Result (Result) import Vulkan.Core10.Enums.Result (Result(..)) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion (SamplerYcbcrConversionInfo) import Vulkan.CStruct.Extends (SomeStruct) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Exception (VulkanException(..)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO)) import Vulkan.Core10.Enums.Result (Result(SUCCESS)) import Vulkan.Core10.Enums.ComponentSwizzle (ComponentSwizzle(..)) import Vulkan.Core10.Handles (ImageView(..)) import Vulkan.Core10.Enums.ImageViewCreateFlagBits (ImageViewCreateFlagBits(..)) import Vulkan.Core10.Enums.ImageViewCreateFlagBits (ImageViewCreateFlags) import Vulkan.Core10.Enums.ImageViewType (ImageViewType(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCreateImageView :: FunPtr (Ptr Device_T -> Ptr (SomeStruct ImageViewCreateInfo) -> Ptr AllocationCallbacks -> Ptr ImageView -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct ImageViewCreateInfo) -> Ptr AllocationCallbacks -> Ptr ImageView -> IO Result -- | vkCreateImageView - Create an image view from an existing image -- -- == Valid Usage -- -- - #VUID-vkCreateImageView-image-09179# 'ImageViewCreateInfo'::@image@ -- /must/ have been created from @device@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCreateImageView-device-parameter# @device@ /must/ be a valid -- 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkCreateImageView-pCreateInfo-parameter# @pCreateInfo@ /must/ -- be a valid pointer to a valid 'ImageViewCreateInfo' structure -- -- - #VUID-vkCreateImageView-pAllocator-parameter# If @pAllocator@ is not -- @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkCreateImageView-pView-parameter# @pView@ /must/ be a valid -- pointer to a 'Vulkan.Core10.Handles.ImageView' handle -- -- == 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_OUT_OF_DEVICE_MEMORY' -- -- - 'Vulkan.Extensions.VK_KHR_buffer_device_address.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.ImageView', -- 'ImageViewCreateInfo' createImageView :: forall a io . (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => -- | @device@ is the logical device that creates the image view. Device -> -- | @pCreateInfo@ is a pointer to a 'ImageViewCreateInfo' structure -- containing parameters to be used to create the image view. (ImageViewCreateInfo a) -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io (ImageView) createImageView :: forall (a :: [*]) (io :: * -> *). (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageViewCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io ImageView createImageView Device device ImageViewCreateInfo a createInfo "allocator" ::: Maybe AllocationCallbacks allocator = 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 vkCreateImageViewPtr :: FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result) vkCreateImageViewPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result) pVkCreateImageView (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 -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result) vkCreateImageViewPtr 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 vkCreateImageView is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCreateImageView' :: Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result vkCreateImageView' = FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result) -> Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result mkVkCreateImageView FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result) vkCreateImageViewPtr Ptr (ImageViewCreateInfo a) pCreateInfo <- 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 (ImageViewCreateInfo a createInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> 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 (AllocationCallbacks j) "pView" ::: Ptr ImageView pPView <- 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 c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket (forall a. Int -> IO (Ptr a) callocBytes @ImageView Int 8) forall a. Ptr a -> IO () free 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 "vkCreateImageView" (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pView" ::: Ptr ImageView) -> IO Result vkCreateImageView' (Device -> Ptr Device_T deviceHandle (Device device)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions Ptr (ImageViewCreateInfo a) pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator ("pView" ::: Ptr ImageView pPView)) 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)) ImageView pView <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> IO a peek @ImageView "pView" ::: Ptr ImageView pPView forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ (ImageView pView) -- | A convenience wrapper to make a compatible pair of calls to -- 'createImageView' and 'destroyImageView' -- -- To ensure that 'destroyImageView' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withImageView :: forall a io r . (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageViewCreateInfo a -> Maybe AllocationCallbacks -> (io ImageView -> (ImageView -> io ()) -> r) -> r withImageView :: forall (a :: [*]) (io :: * -> *) r. (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageViewCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> (io ImageView -> (ImageView -> io ()) -> r) -> r withImageView Device device ImageViewCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator io ImageView -> (ImageView -> io ()) -> r b = io ImageView -> (ImageView -> io ()) -> r b (forall (a :: [*]) (io :: * -> *). (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageViewCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io ImageView createImageView Device device ImageViewCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator) (\(ImageView o0) -> forall (io :: * -> *). MonadIO io => Device -> ImageView -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyImageView Device device ImageView o0 "allocator" ::: Maybe AllocationCallbacks pAllocator) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkDestroyImageView :: FunPtr (Ptr Device_T -> ImageView -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> ImageView -> Ptr AllocationCallbacks -> IO () -- | vkDestroyImageView - Destroy an image view object -- -- == Valid Usage -- -- - #VUID-vkDestroyImageView-imageView-01026# All submitted commands -- that refer to @imageView@ /must/ have completed execution -- -- - #VUID-vkDestroyImageView-imageView-01027# If -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @imageView@ was created, a compatible set of callbacks -- /must/ be provided here -- -- - #VUID-vkDestroyImageView-imageView-01028# If no -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @imageView@ was created, @pAllocator@ /must/ be @NULL@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkDestroyImageView-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkDestroyImageView-imageView-parameter# If @imageView@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', @imageView@ /must/ be a -- valid 'Vulkan.Core10.Handles.ImageView' handle -- -- - #VUID-vkDestroyImageView-pAllocator-parameter# If @pAllocator@ is -- not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkDestroyImageView-imageView-parent# If @imageView@ is a valid -- handle, it /must/ have been created, allocated, or retrieved from -- @device@ -- -- == Host Synchronization -- -- - Host access to @imageView@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.ImageView' destroyImageView :: forall io . (MonadIO io) => -- | @device@ is the logical device that destroys the image view. Device -> -- | @imageView@ is the image view to destroy. ImageView -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyImageView :: forall (io :: * -> *). MonadIO io => Device -> ImageView -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyImageView Device device ImageView imageView "allocator" ::: Maybe AllocationCallbacks allocator = 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 vkDestroyImageViewPtr :: FunPtr (Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyImageViewPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) pVkDestroyImageView (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 -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyImageViewPtr 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 vkDestroyImageView is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkDestroyImageView' :: Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyImageView' = FunPtr (Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () mkVkDestroyImageView FunPtr (Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyImageViewPtr "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> 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 (AllocationCallbacks j) 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 "vkDestroyImageView" (Ptr Device_T -> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyImageView' (Device -> Ptr Device_T deviceHandle (Device device)) (ImageView imageView) "pAllocator" ::: Ptr AllocationCallbacks pAllocator) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () -- | VkComponentMapping - Structure specifying a color component mapping -- -- == Valid Usage (Implicit) -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferFormatProperties2ANDROID', -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferFormatPropertiesANDROID', -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionPropertiesFUCHSIA', -- 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle', -- 'ImageViewCreateInfo', -- 'Vulkan.Extensions.VK_EXT_border_color_swizzle.SamplerBorderColorComponentMappingCreateInfoEXT', -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo', -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.ScreenBufferFormatPropertiesQNX', -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkVideoFormatPropertiesKHR VkVideoFormatPropertiesKHR> data ComponentMapping = ComponentMapping { -- | @r@ is a 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' -- specifying the component value placed in the R component of the output -- vector. -- -- #VUID-VkComponentMapping-r-parameter# @r@ /must/ be a valid -- 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' value ComponentMapping -> ComponentSwizzle r :: ComponentSwizzle , -- | @g@ is a 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' -- specifying the component value placed in the G component of the output -- vector. -- -- #VUID-VkComponentMapping-g-parameter# @g@ /must/ be a valid -- 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' value ComponentMapping -> ComponentSwizzle g :: ComponentSwizzle , -- | @b@ is a 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' -- specifying the component value placed in the B component of the output -- vector. -- -- #VUID-VkComponentMapping-b-parameter# @b@ /must/ be a valid -- 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' value ComponentMapping -> ComponentSwizzle b :: ComponentSwizzle , -- | @a@ is a 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' -- specifying the component value placed in the A component of the output -- vector. -- -- #VUID-VkComponentMapping-a-parameter# @a@ /must/ be a valid -- 'Vulkan.Core10.Enums.ComponentSwizzle.ComponentSwizzle' value ComponentMapping -> ComponentSwizzle a :: ComponentSwizzle } deriving (Typeable, ComponentMapping -> ComponentMapping -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ComponentMapping -> ComponentMapping -> Bool $c/= :: ComponentMapping -> ComponentMapping -> Bool == :: ComponentMapping -> ComponentMapping -> Bool $c== :: ComponentMapping -> ComponentMapping -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (ComponentMapping) #endif deriving instance Show ComponentMapping instance ToCStruct ComponentMapping where withCStruct :: forall b. ComponentMapping -> (Ptr ComponentMapping -> IO b) -> IO b withCStruct ComponentMapping x Ptr ComponentMapping -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 16 forall a b. (a -> b) -> a -> b $ \Ptr ComponentMapping p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr ComponentMapping p ComponentMapping x (Ptr ComponentMapping -> IO b f Ptr ComponentMapping p) pokeCStruct :: forall b. Ptr ComponentMapping -> ComponentMapping -> IO b -> IO b pokeCStruct Ptr ComponentMapping p ComponentMapping{ComponentSwizzle a :: ComponentSwizzle b :: ComponentSwizzle g :: ComponentSwizzle r :: ComponentSwizzle $sel:a:ComponentMapping :: ComponentMapping -> ComponentSwizzle $sel:b:ComponentMapping :: ComponentMapping -> ComponentSwizzle $sel:g:ComponentMapping :: ComponentMapping -> ComponentSwizzle $sel:r:ComponentMapping :: ComponentMapping -> ComponentSwizzle ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ComponentSwizzle)) (ComponentSwizzle r) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ComponentSwizzle)) (ComponentSwizzle g) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr ComponentSwizzle)) (ComponentSwizzle b) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr ComponentSwizzle)) (ComponentSwizzle a) IO b f cStructSize :: Int cStructSize = Int 16 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr ComponentMapping -> IO b -> IO b pokeZeroCStruct Ptr ComponentMapping p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ComponentSwizzle)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ComponentSwizzle)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr ComponentSwizzle)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr ComponentSwizzle)) (forall a. Zero a => a zero) IO b f instance FromCStruct ComponentMapping where peekCStruct :: Ptr ComponentMapping -> IO ComponentMapping peekCStruct Ptr ComponentMapping p = do ComponentSwizzle r <- forall a. Storable a => Ptr a -> IO a peek @ComponentSwizzle ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ComponentSwizzle)) ComponentSwizzle g <- forall a. Storable a => Ptr a -> IO a peek @ComponentSwizzle ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ComponentSwizzle)) ComponentSwizzle b <- forall a. Storable a => Ptr a -> IO a peek @ComponentSwizzle ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr ComponentSwizzle)) ComponentSwizzle a <- forall a. Storable a => Ptr a -> IO a peek @ComponentSwizzle ((Ptr ComponentMapping p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr ComponentSwizzle)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ComponentSwizzle -> ComponentSwizzle -> ComponentSwizzle -> ComponentSwizzle -> ComponentMapping ComponentMapping ComponentSwizzle r ComponentSwizzle g ComponentSwizzle b ComponentSwizzle a instance Storable ComponentMapping where sizeOf :: ComponentMapping -> Int sizeOf ~ComponentMapping _ = Int 16 alignment :: ComponentMapping -> Int alignment ~ComponentMapping _ = Int 4 peek :: Ptr ComponentMapping -> IO ComponentMapping peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr ComponentMapping -> ComponentMapping -> IO () poke Ptr ComponentMapping ptr ComponentMapping poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr ComponentMapping ptr ComponentMapping poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ComponentMapping where zero :: ComponentMapping zero = ComponentSwizzle -> ComponentSwizzle -> ComponentSwizzle -> ComponentSwizzle -> ComponentMapping ComponentMapping forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageSubresourceRange - Structure specifying an image subresource -- range -- -- = Description -- -- The number of mipmap levels and array layers /must/ be a subset of the -- image subresources in the image. If an application wants to use all mip -- levels or layers in an image after the @baseMipLevel@ or -- @baseArrayLayer@, it /can/ set @levelCount@ and @layerCount@ to the -- special values 'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS' and -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' without knowing the -- exact number of mip levels or layers. -- -- For cube and cube array image views, the layers of the image view -- starting at @baseArrayLayer@ correspond to faces in the order +X, -X, -- +Y, -Y, +Z, -Z. For cube arrays, each set of six sequential layers is a -- single cube, so the number of cube maps in a cube map array view is -- /@layerCount@ \/ 6/, and image array layer (@baseArrayLayer@ + i) is -- face index (i mod 6) of cube /i \/ 6/. If the number of layers in the -- view, whether set explicitly in @layerCount@ or implied by -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', is not a multiple -- of 6, the last cube map in the array /must/ not be accessed. -- -- @aspectMask@ /must/ be only -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' if -- @format@ is a color, depth-only or stencil-only format, respectively, -- except if @format@ is a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>. -- If using a depth\/stencil format with both depth and stencil components, -- @aspectMask@ /must/ include at least one of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' and -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', and -- /can/ include both. -- -- When the 'ImageSubresourceRange' structure is used to select a subset of -- the slices of a 3D image’s mip level in order to create a 2D or 2D array -- image view of a 3D image created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT', -- @baseArrayLayer@ and @layerCount@ specify the first slice index and the -- number of slices to include in the created image view. Such an image -- view /can/ be used as a framebuffer attachment that refers only to the -- specified range of slices of the selected mip level. However, any layout -- transitions performed on such an attachment view during a render pass -- instance still apply to the entire subresource referenced which includes -- all the slices of the selected mip level. -- -- When using an image view of a depth\/stencil image to populate a -- descriptor set (e.g. for sampling in the shader, or for use as an input -- attachment), the @aspectMask@ /must/ only include one bit, which selects -- whether the image view is used for depth reads (i.e. using a -- floating-point sampler or input attachment in the shader) or stencil -- reads (i.e. using an unsigned integer sampler or input attachment in the -- shader). When an image view of a depth\/stencil image is used as a -- depth\/stencil framebuffer attachment, the @aspectMask@ is ignored and -- both depth and stencil image subresources are used. -- -- When creating a 'Vulkan.Core10.Handles.ImageView', if -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion> -- is enabled in the sampler, the @aspectMask@ of a @subresourceRange@ used -- by the 'Vulkan.Core10.Handles.ImageView' /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'. -- -- When creating a 'Vulkan.Core10.Handles.ImageView', if sampler Y′CBCR -- conversion is not enabled in the sampler and the image @format@ is -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar>, -- the image /must/ have been created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT', -- and the @aspectMask@ of the 'Vulkan.Core10.Handles.ImageView'’s -- @subresourceRange@ /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'. -- -- == Valid Usage -- -- - #VUID-VkImageSubresourceRange-levelCount-01720# If @levelCount@ is -- not 'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS', it /must/ be -- greater than @0@ -- -- - #VUID-VkImageSubresourceRange-layerCount-01721# If @layerCount@ is -- not 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', it /must/ -- be greater than @0@ -- -- - #VUID-VkImageSubresourceRange-aspectMask-01670# If @aspectMask@ -- includes -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', -- then it /must/ not include any of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', -- or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' -- -- - #VUID-VkImageSubresourceRange-aspectMask-02278# @aspectMask@ /must/ -- not include @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index -- /i/ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageSubresourceRange-aspectMask-parameter# @aspectMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values -- -- - #VUID-VkImageSubresourceRange-aspectMask-requiredbitmask# -- @aspectMask@ /must/ not be @0@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Extensions.VK_EXT_host_image_copy.HostImageLayoutTransitionInfoEXT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags', -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier', -- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.ImageMemoryBarrier2', -- 'ImageViewCreateInfo', -- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage', -- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage' data ImageSubresourceRange = ImageSubresourceRange { -- | @aspectMask@ is a bitmask of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' specifying -- which aspect(s) of the image are included in the view. ImageSubresourceRange -> ImageAspectFlags aspectMask :: ImageAspectFlags , -- | @baseMipLevel@ is the first mipmap level accessible to the view. ImageSubresourceRange -> Word32 baseMipLevel :: Word32 , -- | @levelCount@ is the number of mipmap levels (starting from -- @baseMipLevel@) accessible to the view. ImageSubresourceRange -> Word32 levelCount :: Word32 , -- | @baseArrayLayer@ is the first array layer accessible to the view. ImageSubresourceRange -> Word32 baseArrayLayer :: Word32 , -- | @layerCount@ is the number of array layers (starting from -- @baseArrayLayer@) accessible to the view. ImageSubresourceRange -> Word32 layerCount :: Word32 } deriving (Typeable, ImageSubresourceRange -> ImageSubresourceRange -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ImageSubresourceRange -> ImageSubresourceRange -> Bool $c/= :: ImageSubresourceRange -> ImageSubresourceRange -> Bool == :: ImageSubresourceRange -> ImageSubresourceRange -> Bool $c== :: ImageSubresourceRange -> ImageSubresourceRange -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (ImageSubresourceRange) #endif deriving instance Show ImageSubresourceRange instance ToCStruct ImageSubresourceRange where withCStruct :: forall b. ImageSubresourceRange -> (Ptr ImageSubresourceRange -> IO b) -> IO b withCStruct ImageSubresourceRange x Ptr ImageSubresourceRange -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 20 forall a b. (a -> b) -> a -> b $ \Ptr ImageSubresourceRange p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr ImageSubresourceRange p ImageSubresourceRange x (Ptr ImageSubresourceRange -> IO b f Ptr ImageSubresourceRange p) pokeCStruct :: forall b. Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b pokeCStruct Ptr ImageSubresourceRange p ImageSubresourceRange{Word32 ImageAspectFlags layerCount :: Word32 baseArrayLayer :: Word32 levelCount :: Word32 baseMipLevel :: Word32 aspectMask :: ImageAspectFlags $sel:layerCount:ImageSubresourceRange :: ImageSubresourceRange -> Word32 $sel:baseArrayLayer:ImageSubresourceRange :: ImageSubresourceRange -> Word32 $sel:levelCount:ImageSubresourceRange :: ImageSubresourceRange -> Word32 $sel:baseMipLevel:ImageSubresourceRange :: ImageSubresourceRange -> Word32 $sel:aspectMask:ImageSubresourceRange :: ImageSubresourceRange -> ImageAspectFlags ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags aspectMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (Word32 baseMipLevel) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (Word32 levelCount) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) (Word32 baseArrayLayer) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (Word32 layerCount) IO b f cStructSize :: Int cStructSize = Int 20 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr ImageSubresourceRange -> IO b -> IO b pokeZeroCStruct Ptr ImageSubresourceRange p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct ImageSubresourceRange where peekCStruct :: Ptr ImageSubresourceRange -> IO ImageSubresourceRange peekCStruct Ptr ImageSubresourceRange p = do ImageAspectFlags aspectMask <- forall a. Storable a => Ptr a -> IO a peek @ImageAspectFlags ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ImageAspectFlags)) Word32 baseMipLevel <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) Word32 levelCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) Word32 baseArrayLayer <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr Word32)) Word32 layerCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ImageSubresourceRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ImageAspectFlags -> Word32 -> Word32 -> Word32 -> Word32 -> ImageSubresourceRange ImageSubresourceRange ImageAspectFlags aspectMask Word32 baseMipLevel Word32 levelCount Word32 baseArrayLayer Word32 layerCount instance Storable ImageSubresourceRange where sizeOf :: ImageSubresourceRange -> Int sizeOf ~ImageSubresourceRange _ = Int 20 alignment :: ImageSubresourceRange -> Int alignment ~ImageSubresourceRange _ = Int 4 peek :: Ptr ImageSubresourceRange -> IO ImageSubresourceRange peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO () poke Ptr ImageSubresourceRange ptr ImageSubresourceRange poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr ImageSubresourceRange ptr ImageSubresourceRange poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero ImageSubresourceRange where zero :: ImageSubresourceRange zero = ImageAspectFlags -> Word32 -> Word32 -> Word32 -> Word32 -> ImageSubresourceRange ImageSubresourceRange forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkImageViewCreateInfo - Structure specifying parameters of a newly -- created image view -- -- = Description -- -- Some of the @image@ creation parameters are inherited by the view. In -- particular, image view creation inherits the implicit parameter @usage@ -- specifying the allowed usages of the image view that, by default, takes -- the value of the corresponding @usage@ parameter specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' at image creation time. The -- implicit @usage@ /can/ be overridden by adding a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure to the @pNext@ chain, but the view usage /must/ be a subset of -- the image usage. If @image@ has a depth-stencil format and was created -- with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Image.ImageCreateInfo', the usage is calculated based on -- the @subresource.aspectMask@ provided: -- -- - If @aspectMask@ includes only -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- the implicit @usage@ is equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo'::@stencilUsage@. -- -- - If @aspectMask@ includes only -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT', -- the implicit @usage@ is equal to -- 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@. -- -- - If both aspects are included in @aspectMask@, the implicit @usage@ -- is equal to the intersection of -- 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@ and -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo'::@stencilUsage@. -- -- If @image@ is a 3D image, its Z range /can/ be restricted to a subset by -- adding a -- 'Vulkan.Extensions.VK_EXT_image_sliced_view_of_3d.ImageViewSlicedCreateInfoEXT' -- to the @pNext@ chain. -- -- If @image@ was created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT' -- flag, and if the @format@ of the image is not -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar>, -- @format@ /can/ be different from the image’s format, but if @image@ was -- created without the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT' -- flag and they are not equal they /must/ be /compatible/. Image format -- compatibility is defined in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatibility-classes Format Compatibility Classes> -- section. Views of compatible formats will have the same mapping between -- texel coordinates and memory locations irrespective of the @format@, -- with only the interpretation of the bit pattern changing. -- -- If @image@ was created with a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- format, and the image view’s @aspectMask@ is one of -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT', the -- view’s aspect mask is considered to be equivalent to -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' when -- used as a framebuffer attachment. -- -- Note -- -- Values intended to be used with one view format /may/ not be exactly -- preserved when written or read through a different format. For example, -- an integer value that happens to have the bit pattern of a floating -- point denorm or NaN /may/ be flushed or canonicalized when written or -- read through a view with a floating point format. Similarly, a value -- written through a signed normalized format that has a bit pattern -- exactly equal to -2b /may/ be changed to -2b + 1 as described in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fundamentals-fixedfpconv Conversion from Normalized Fixed-Point to Floating-Point>. -- -- If @image@ was created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT' -- flag, @format@ /must/ be /compatible/ with the image’s format as -- described above; or /must/ be an uncompressed format, in which case it -- /must/ be -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-size-compatibility size-compatible> -- with the image’s format. In this case, the resulting image view’s texel -- dimensions equal the dimensions of the selected mip level divided by the -- compressed texel block size and rounded up. -- -- The 'ComponentMapping' @components@ member describes a remapping from -- components of the image to components of the vector returned by shader -- image instructions. This remapping /must/ be the identity swizzle for -- storage image descriptors, input attachment descriptors, framebuffer -- attachments, and any 'Vulkan.Core10.Handles.ImageView' used with a -- combined image sampler that enables -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>. -- -- If the image view is to be used with a sampler which supports -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- an /identically defined object/ of type -- 'Vulkan.Core11.Handles.SamplerYcbcrConversion' to that used to create -- the sampler /must/ be passed to 'createImageView' in a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- included in the @pNext@ chain of 'ImageViewCreateInfo'. Conversely, if a -- 'Vulkan.Core11.Handles.SamplerYcbcrConversion' object is passed to -- 'createImageView', an identically defined -- 'Vulkan.Core11.Handles.SamplerYcbcrConversion' object /must/ be used -- when sampling the image. -- -- If the image has a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- @format@, @subresourceRange.aspectMask@ is -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', and -- @usage@ includes -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', then -- the @format@ /must/ be identical to the image @format@ and the sampler -- to be used with the image view /must/ enable -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>. -- -- When such an image is used in a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#video-coding video coding> -- operation, the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion> -- has no effect. -- -- If @image@ was created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT' -- and the image has a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- @format@, and if @subresourceRange.aspectMask@ is -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT', -- @format@ /must/ be -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatible-planes compatible> -- with the corresponding plane of the image, and the sampler to be used -- with the image view /must/ not enable -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>. -- The @width@ and @height@ of the single-plane image view /must/ be -- derived from the multi-planar image’s dimensions in the manner listed -- for -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatible-planes plane compatibility> -- for the plane. -- -- Any view of an image plane will have the same mapping between texel -- coordinates and memory locations as used by the components of the color -- aspect, subject to the formulae relating texel coordinates to -- lower-resolution planes as described in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-chroma-reconstruction Chroma Reconstruction>. -- That is, if an R or B plane has a reduced resolution relative to the G -- plane of the multi-planar image, the image view operates using the -- (/uplane/, /vplane/) unnormalized coordinates of the reduced-resolution -- plane, and these coordinates access the same memory locations as the -- (/ucolor/, /vcolor/) unnormalized coordinates of the color aspect for -- which chroma reconstruction operations operate on the same (/uplane/, -- /vplane/) or (/iplane/, /jplane/) coordinates. -- -- +----------------------------------------------------------------+-----------------------------------------------+ -- | Image View Type | Compatible Image Types | -- +================================================================+===============================================+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' | -- | | , | -- | | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' | -- | | , | -- | | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- | 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D' | 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' | -- +----------------------------------------------------------------+-----------------------------------------------+ -- -- Image type and image view type compatibility requirements -- -- == Valid Usage -- -- - #VUID-VkImageViewCreateInfo-image-01003# If @image@ was not created -- with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CUBE_COMPATIBLE_BIT' -- then @viewType@ /must/ not be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-viewType-01004# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-imageCubeArray imageCubeArray> -- feature is not enabled, @viewType@ /must/ not be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-image-06723# If @image@ was created with -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' but without -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- set then @viewType@ /must/ not be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-image-06728# If @image@ was created with -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' but without -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- or -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT' -- set, then @viewType@ /must/ not be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' -- -- - #VUID-VkImageViewCreateInfo-image-04970# If @image@ was created with -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' then -- @subresourceRange.levelCount@ /must/ be 1 -- -- - #VUID-VkImageViewCreateInfo-image-04971# If @image@ was created with -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D' and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' then -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ /must/ not contain -- any of -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_BINDING_BIT', -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT', -- and -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_ALIASED_BIT' -- -- - #VUID-VkImageViewCreateInfo-image-04972# If @image@ was created with -- a @samples@ value not equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' then -- @viewType@ /must/ be either -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-image-04441# @image@ /must/ have been -- created with a @usage@ value containing at least one of the usages -- defined in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#valid-imageview-imageusage valid image usage> -- list for image views -- -- - #VUID-VkImageViewCreateInfo-None-02273# The -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- of the resultant image view /must/ contain at least one bit -- -- - #VUID-VkImageViewCreateInfo-usage-02274# If @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', -- then the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- of the resultant image view /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT' -- -- - #VUID-VkImageViewCreateInfo-usage-02275# If @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_STORAGE_BIT', -- then the image view’s -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_BIT' -- -- - #VUID-VkImageViewCreateInfo-usage-08931# If @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT', -- then the image view’s -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' -- or -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-VkImageViewCreateInfo-usage-02277# If @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT', -- then the image view’s -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkImageViewCreateInfo-usage-08932# If @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT', -- and any of the following is true: -- -- - the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-externalFormatResolve externalFormatResolve> -- feature is not enabled -- -- - the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-nullColorAttachmentWithExternalFormatResolve nullColorAttachmentWithExternalFormatResolve> -- property is 'Vulkan.Core10.FundamentalTypes.FALSE' -- -- - @image@ was created with an -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value of 0 -- -- then the image view’s -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain at least one of -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' -- or -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' -- or -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-01478# -- @subresourceRange.baseMipLevel@ /must/ be less than the @mipLevels@ -- specified in 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was -- created -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-01718# If -- @subresourceRange.levelCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS', -- @subresourceRange.baseMipLevel@ + @subresourceRange.levelCount@ -- /must/ be less than or equal to the @mipLevels@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created -- -- - #VUID-VkImageViewCreateInfo-image-02571# If @image@ was created with -- @usage@ containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT', -- @subresourceRange.levelCount@ /must/ be @1@ -- -- - #VUID-VkImageViewCreateInfo-image-06724# If @image@ is not a 3D -- image created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- or -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT' -- set, or @viewType@ is not -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', -- @subresourceRange.baseArrayLayer@ /must/ be less than the -- @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' -- when @image@ was created -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-06725# If -- @subresourceRange.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', @image@ is not -- a 3D image created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- or -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT' -- set, or @viewType@ is not -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', -- @subresourceRange.layerCount@ /must/ be non-zero and -- @subresourceRange.baseArrayLayer@ + @subresourceRange.layerCount@ -- /must/ be less than or equal to the @arrayLayers@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created -- -- - #VUID-VkImageViewCreateInfo-image-02724# If @image@ is a 3D image -- created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- set, and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', -- @subresourceRange.baseArrayLayer@ /must/ be less than the depth -- computed from @baseMipLevel@ and @extent.depth@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created, -- according to the formula defined in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-mip-level-sizing Image Mip Level Sizing> -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-02725# If -- @subresourceRange.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', @image@ is a 3D -- image created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT' -- set, and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', -- @subresourceRange.layerCount@ /must/ be non-zero and -- @subresourceRange.baseArrayLayer@ + @subresourceRange.layerCount@ -- /must/ be less than or equal to the depth computed from -- @baseMipLevel@ and @extent.depth@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @image@ was created, -- according to the formula defined in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-mip-level-sizing Image Mip Level Sizing> -- -- - #VUID-VkImageViewCreateInfo-image-01761# If @image@ was created with -- the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT' -- flag, but without the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT' -- flag, and if the @format@ of the @image@ is not a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- format, @format@ /must/ be compatible with the @format@ used to -- create @image@, as defined in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatibility-classes Format Compatibility Classes> -- -- - #VUID-VkImageViewCreateInfo-image-01583# If @image@ was created with -- the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT' -- flag, @format@ /must/ be compatible with, or /must/ be an -- uncompressed format that is size-compatible with, the @format@ used -- to create @image@ -- -- - #VUID-VkImageViewCreateInfo-image-07072# If @image@ was created with -- the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT' -- flag and @format@ is a non-compressed format, the @levelCount@ and -- @layerCount@ members of @subresourceRange@ /must/ both be @1@ -- -- - #VUID-VkImageViewCreateInfo-pNext-01585# If a -- 'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo' -- structure was included in the @pNext@ chain of the -- 'Vulkan.Core10.Image.ImageCreateInfo' structure used when creating -- @image@ and -- 'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@viewFormatCount@ -- is not zero then @format@ /must/ be one of the formats in -- 'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@pViewFormats@ -- -- - #VUID-VkImageViewCreateInfo-image-01586# If @image@ was created with -- the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT' -- flag, if the @format@ of the @image@ is a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- format, and if @subresourceRange.aspectMask@ is one of the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bits, then @format@ /must/ be compatible with the -- 'Vulkan.Core10.Enums.Format.Format' for the plane of the @image@ -- @format@ indicated by @subresourceRange.aspectMask@, as defined in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-compatible-planes> -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-07818# -- @subresourceRange.aspectMask@ /must/ only have at most 1 valid -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-planes-image-aspect multi-planar aspect mask> -- bit -- -- - #VUID-VkImageViewCreateInfo-image-01762# If @image@ was not created -- with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT' -- flag, or if the @format@ of the @image@ is a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- format and if @subresourceRange.aspectMask@ is -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', -- @format@ /must/ be identical to the @format@ used to create @image@ -- -- - #VUID-VkImageViewCreateInfo-format-06415# If the image view -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#image-views-requiring-sampler-ycbcr-conversion requires a sampler Y′CBCR conversion> -- and @usage@ contains -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', -- then the @pNext@ chain /must/ include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- structure with a conversion value other than -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-VkImageViewCreateInfo-format-04714# If @format@ has a @_422@ -- or @_420@ suffix then @image@ /must/ have been created with a width -- that is a multiple of 2 -- -- - #VUID-VkImageViewCreateInfo-format-04715# If @format@ has a @_420@ -- suffix then @image@ /must/ have been created with a height that is a -- multiple of 2 -- -- - #VUID-VkImageViewCreateInfo-pNext-01970# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- structure with a @conversion@ value other than -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', all members of -- @components@ /must/ have the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-identity-mappings identity swizzle> -- -- - #VUID-VkImageViewCreateInfo-pNext-06658# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- structure with a @conversion@ value other than -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', @format@ /must/ be the -- same used in -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'::@format@ -- -- - #VUID-VkImageViewCreateInfo-image-01020# If @image@ is non-sparse -- then it /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-VkImageViewCreateInfo-subResourceRange-01021# @viewType@ -- /must/ be compatible with the type of @image@ as shown in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-compatibility view type compatibility table> -- -- - #VUID-VkImageViewCreateInfo-image-02399# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-external-formats Android external format>, -- @format@ /must/ be 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-VkImageViewCreateInfo-image-02400# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-external-formats Android external format>, -- the @pNext@ chain /must/ include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- structure with a @conversion@ object created with the same external -- format as @image@ -- -- - #VUID-VkImageViewCreateInfo-image-02401# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-external-formats Android external format>, -- all members of @components@ /must/ be the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-identity-mappings identity swizzle> -- -- - #VUID-VkImageViewCreateInfo-image-08957# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-screen-buffer-external-formats QNX Screen external format>, -- @format@ /must/ be 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' -- -- - #VUID-VkImageViewCreateInfo-image-08958# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-screen-buffer-external-formats QNX Screen external format>, -- the @pNext@ chain /must/ include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- structure with a @conversion@ object created with the same external -- format as @image@ -- -- - #VUID-VkImageViewCreateInfo-image-08959# If @image@ has an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-screen-buffer-external-formats QNX Screen external format>, -- all members of @components@ /must/ be the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-identity-mappings identity swizzle> -- -- - #VUID-VkImageViewCreateInfo-image-02086# If @image@ was created with -- @usage@ containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR', -- @viewType@ /must/ be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-image-02087# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- feature is enabled, and If @image@ was created with @usage@ -- containing -- 'Vulkan.Extensions.VK_NV_shading_rate_image.IMAGE_USAGE_SHADING_RATE_IMAGE_BIT_NV', -- @format@ /must/ be 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT' -- -- - #VUID-VkImageViewCreateInfo-usage-04550# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- feature is enabled, and the @usage@ for the image view includes -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR', -- then the image view’s -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-VkImageViewCreateInfo-usage-04551# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- feature is enabled, the @usage@ for the image view includes -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR', -- and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-layeredShadingRateAttachments layeredShadingRateAttachments> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', -- @subresourceRange.layerCount@ /must/ be @1@ -- -- - #VUID-VkImageViewCreateInfo-flags-02572# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-fragmentDensityMapDynamic fragmentDensityMapDynamic> -- feature is not enabled, @flags@ /must/ not contain -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT' -- -- - #VUID-VkImageViewCreateInfo-flags-03567# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-fragmentDensityMapDeferred fragmentDensityMapDeferred> -- feature is not enabled, @flags@ /must/ not contain -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT' -- -- - #VUID-VkImageViewCreateInfo-flags-03568# If @flags@ contains -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT', -- @flags@ /must/ not contain -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT' -- -- - #VUID-VkImageViewCreateInfo-image-03569# If @image@ was created with -- @flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- and @usage@ containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT', -- @subresourceRange.layerCount@ /must/ be less than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxSubsampledArrayLayers ::maxSubsampledArrayLayers> -- -- - #VUID-VkImageViewCreateInfo-invocationMask-04993# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-invocationMask invocationMask> -- feature is enabled, and if @image@ was created with @usage@ -- containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INVOCATION_MASK_BIT_HUAWEI', -- @format@ /must/ be 'Vulkan.Core10.Enums.Format.FORMAT_R8_UINT' -- -- - #VUID-VkImageViewCreateInfo-flags-04116# If @flags@ does not contain -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT' -- and @image@ was created with @usage@ containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT', -- its @flags@ /must/ not contain any of -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_PROTECTED_BIT', -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_BINDING_BIT', -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT', -- or -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_ALIASED_BIT' -- -- - #VUID-VkImageViewCreateInfo-pNext-02662# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure, and @image@ was not created with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Image.ImageCreateInfo', its @usage@ member /must/ not -- include any bits that were not set in the @usage@ member of the -- 'Vulkan.Core10.Image.ImageCreateInfo' structure used to create -- @image@ -- -- - #VUID-VkImageViewCreateInfo-pNext-02663# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure, @image@ was created with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Image.ImageCreateInfo', and -- @subresourceRange.aspectMask@ includes -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- the @usage@ member of the -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure /must/ not include any bits that were not set in the -- @usage@ member of the -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo' -- structure used to create @image@ -- -- - #VUID-VkImageViewCreateInfo-pNext-02664# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure, @image@ was created with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo' -- structure included in the @pNext@ chain of -- 'Vulkan.Core10.Image.ImageCreateInfo', and -- @subresourceRange.aspectMask@ includes bits other than -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', -- the @usage@ member of the -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo' -- structure /must/ not include any bits that were not set in the -- @usage@ member of the 'Vulkan.Core10.Image.ImageCreateInfo' -- structure used to create @image@ -- -- - #VUID-VkImageViewCreateInfo-imageViewType-04973# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D'; and -- @subresourceRange.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', then -- @subresourceRange.layerCount@ /must/ be 1 -- -- - #VUID-VkImageViewCreateInfo-imageViewType-04974# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D'; and -- @subresourceRange.layerCount@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', then the -- remaining number of layers /must/ be 1 -- -- - #VUID-VkImageViewCreateInfo-viewType-02960# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE' and -- @subresourceRange.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', -- @subresourceRange.layerCount@ /must/ be @6@ -- -- - #VUID-VkImageViewCreateInfo-viewType-02961# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' and -- @subresourceRange.layerCount@ is not -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', -- @subresourceRange.layerCount@ /must/ be a multiple of @6@ -- -- - #VUID-VkImageViewCreateInfo-viewType-02962# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE' and -- @subresourceRange.layerCount@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the remaining -- number of layers /must/ be @6@ -- -- - #VUID-VkImageViewCreateInfo-viewType-02963# If @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' and -- @subresourceRange.layerCount@ is -- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', the remaining -- number of layers /must/ be a multiple of @6@ -- -- - #VUID-VkImageViewCreateInfo-imageViewFormatSwizzle-04465# If the -- @VK_KHR_portability_subset@ extension is enabled, and -- 'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@imageViewFormatSwizzle@ -- is 'Vulkan.Core10.FundamentalTypes.FALSE', all elements of -- @components@ /must/ have the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-identity-mappings identity swizzle> -- -- - #VUID-VkImageViewCreateInfo-imageViewFormatReinterpretation-04466# -- If the @VK_KHR_portability_subset@ extension is enabled, and -- 'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@imageViewFormatReinterpretation@ -- is 'Vulkan.Core10.FundamentalTypes.FALSE', the -- 'Vulkan.Core10.Enums.Format.Format' in @format@ /must/ not contain a -- different number of components, or a different number of bits in -- each component, than the format of the 'Vulkan.Core10.Handles.Image' -- in @image@ -- -- - #VUID-VkImageViewCreateInfo-image-04817# If @image@ was created with -- @usage@ containing @VK_IMAGE_USAGE_VIDEO_DECODE_DST_BIT_KHR@, -- @VK_IMAGE_USAGE_VIDEO_DECODE_SRC_BIT_KHR@, or -- @VK_IMAGE_USAGE_VIDEO_DECODE_DPB_BIT_KHR@, then the @viewType@ -- /must/ be 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-image-04818# If @image@ was created with -- @usage@ containing @VK_IMAGE_USAGE_VIDEO_ENCODE_DST_BIT_KHR@, -- @VK_IMAGE_USAGE_VIDEO_ENCODE_SRC_BIT_KHR@, or -- @VK_IMAGE_USAGE_VIDEO_ENCODE_DPB_BIT_KHR@, then the @viewType@ -- /must/ be 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-flags-08106# If @flags@ includes -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT', -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-descriptorBufferCaptureReplay descriptorBufferCaptureReplay> -- feature /must/ be enabled -- -- - #VUID-VkImageViewCreateInfo-pNext-08107# If the @pNext@ chain -- includes a -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.OpaqueCaptureDescriptorDataCreateInfoEXT' -- structure, @flags@ /must/ contain -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT' -- -- - #VUID-VkImageViewCreateInfo-pNext-06787# If the @pNext@ chain -- includes a -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT' -- structure, its @exportObjectType@ member /must/ be -- 'Vulkan.Extensions.VK_EXT_metal_objects.EXPORT_METAL_OBJECT_TYPE_METAL_TEXTURE_BIT_EXT' -- -- - #VUID-VkImageViewCreateInfo-pNext-06944# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-textureSampleWeighted textureSampleWeighted> -- feature /must/ be enabled -- -- - #VUID-VkImageViewCreateInfo-pNext-06945# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then @image@ /must/ have been created with @usage@ -- containing -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLE_WEIGHT_BIT_QCOM' -- -- - #VUID-VkImageViewCreateInfo-pNext-06946# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then @components@ /must/ be -- 'Vulkan.Core10.Enums.ComponentSwizzle.COMPONENT_SWIZZLE_IDENTITY' -- for all components -- -- - #VUID-VkImageViewCreateInfo-pNext-06947# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then @subresourceRange.aspectMask@ /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- -- - #VUID-VkImageViewCreateInfo-pNext-06948# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then @subresourceRange.levelCount@ /must/ be @1@ -- -- - #VUID-VkImageViewCreateInfo-pNext-06949# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure, then @viewType@ /must/ be -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' -- -- - #VUID-VkImageViewCreateInfo-pNext-06950# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and if @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', then -- @image@ /must/ have been created with @imageType@ -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D' -- -- - #VUID-VkImageViewCreateInfo-pNext-06951# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', then -- @subresourceRange.layerCount@ /must/ be equal to @2@ -- -- - #VUID-VkImageViewCreateInfo-pNext-06952# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', then -- @image@ /must/ have been created with @width@ equal to or greater -- than \((numPhases -- \times \mathbin{max}\left( -- \mathbin{align}\left(filterSize.width,4\right), -- filterSize.height\right))\) -- -- - #VUID-VkImageViewCreateInfo-pNext-06953# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and if @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', then -- @image@ /must/ have been created with @imageType@ -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D' -- -- - #VUID-VkImageViewCreateInfo-pNext-06954# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', then -- @subresourceRange.layerCount@ /must/ be equal or greater than -- numPhases -- -- - #VUID-VkImageViewCreateInfo-pNext-06955# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', then -- @image@ /must/ have been created with @width@ equal to or greater -- than @filterSize.width@ -- -- - #VUID-VkImageViewCreateInfo-pNext-06956# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure and @viewType@ is -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY', then -- @image@ /must/ have been created with @height@ equal to or greater -- than @filterSize.height@ -- -- - #VUID-VkImageViewCreateInfo-pNext-06957# If the @pNext@ chain -- includes -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM' -- structure then -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM'::@filterSize.height@ -- /must/ be less than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-weightfilter-maxdimension ::maxWeightFilterDimension.height> -- -- == Valid Usage (Implicit) -- -- - #VUID-VkImageViewCreateInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO' -- -- - #VUID-VkImageViewCreateInfo-pNext-pNext# Each @pNext@ member of any -- structure (including this one) in the @pNext@ chain /must/ be either -- @NULL@ or a pointer to a valid instance of -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT', -- 'Vulkan.Extensions.VK_EXT_astc_decode_mode.ImageViewASTCDecodeModeEXT', -- 'Vulkan.Extensions.VK_EXT_image_view_min_lod.ImageViewMinLodCreateInfoEXT', -- 'Vulkan.Extensions.VK_QCOM_image_processing.ImageViewSampleWeightCreateInfoQCOM', -- 'Vulkan.Extensions.VK_EXT_image_sliced_view_of_3d.ImageViewSlicedCreateInfoEXT', -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.ImageViewUsageCreateInfo', -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.OpaqueCaptureDescriptorDataCreateInfoEXT', -- or -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionInfo' -- -- - #VUID-VkImageViewCreateInfo-sType-unique# The @sType@ value of each -- struct in the @pNext@ chain /must/ be unique, with the exception of -- structures of type -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT' -- -- - #VUID-VkImageViewCreateInfo-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.ImageViewCreateFlagBits' -- values -- -- - #VUID-VkImageViewCreateInfo-image-parameter# @image@ /must/ be a -- valid 'Vulkan.Core10.Handles.Image' handle -- -- - #VUID-VkImageViewCreateInfo-viewType-parameter# @viewType@ /must/ be -- a valid 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' value -- -- - #VUID-VkImageViewCreateInfo-format-parameter# @format@ /must/ be a -- valid 'Vulkan.Core10.Enums.Format.Format' value -- -- - #VUID-VkImageViewCreateInfo-components-parameter# @components@ -- /must/ be a valid 'ComponentMapping' structure -- -- - #VUID-VkImageViewCreateInfo-subresourceRange-parameter# -- @subresourceRange@ /must/ be a valid 'ImageSubresourceRange' -- structure -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'ComponentMapping', 'Vulkan.Core10.Enums.Format.Format', -- 'Vulkan.Core10.Handles.Image', 'ImageSubresourceRange', -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.ImageViewCreateFlags', -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType', -- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createImageView' data ImageViewCreateInfo (es :: [Type]) = ImageViewCreateInfo { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure. forall (es :: [*]). ImageViewCreateInfo es -> Chain es next :: Chain es , -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.ImageViewCreateFlagBits' -- specifying additional parameters of the image view. forall (es :: [*]). ImageViewCreateInfo es -> ImageViewCreateFlags flags :: ImageViewCreateFlags , -- | @image@ is a 'Vulkan.Core10.Handles.Image' on which the view will be -- created. forall (es :: [*]). ImageViewCreateInfo es -> Image image :: Image , -- | @viewType@ is a 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' value -- specifying the type of the image view. forall (es :: [*]). ImageViewCreateInfo es -> ImageViewType viewType :: ImageViewType , -- | @format@ is a 'Vulkan.Core10.Enums.Format.Format' specifying the format -- and type used to interpret texel blocks of the image. forall (es :: [*]). ImageViewCreateInfo es -> Format format :: Format , -- | @components@ is a 'ComponentMapping' structure specifying a remapping of -- color components (or of depth or stencil components after they have been -- converted into color components). forall (es :: [*]). ImageViewCreateInfo es -> ComponentMapping components :: ComponentMapping , -- | @subresourceRange@ is a 'ImageSubresourceRange' structure selecting the -- set of mipmap levels and array layers to be accessible to the view. forall (es :: [*]). ImageViewCreateInfo es -> ImageSubresourceRange subresourceRange :: ImageSubresourceRange } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (ImageViewCreateInfo (es :: [Type])) #endif deriving instance Show (Chain es) => Show (ImageViewCreateInfo es) instance Extensible ImageViewCreateInfo where extensibleTypeName :: String extensibleTypeName = String "ImageViewCreateInfo" setNext :: forall (ds :: [*]) (es :: [*]). ImageViewCreateInfo ds -> Chain es -> ImageViewCreateInfo es setNext ImageViewCreateInfo{Chain ds Format Image ImageSubresourceRange ComponentMapping ImageViewType ImageViewCreateFlags subresourceRange :: ImageSubresourceRange components :: ComponentMapping format :: Format viewType :: ImageViewType image :: Image flags :: ImageViewCreateFlags next :: Chain ds $sel:subresourceRange:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageSubresourceRange $sel:components:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ComponentMapping $sel:format:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Format $sel:viewType:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewType $sel:image:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Image $sel:flags:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewCreateFlags $sel:next:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Chain es ..} Chain es next' = ImageViewCreateInfo{$sel:next:ImageViewCreateInfo :: Chain es next = Chain es next', Format Image ImageSubresourceRange ComponentMapping ImageViewType ImageViewCreateFlags subresourceRange :: ImageSubresourceRange components :: ComponentMapping format :: Format viewType :: ImageViewType image :: Image flags :: ImageViewCreateFlags $sel:subresourceRange:ImageViewCreateInfo :: ImageSubresourceRange $sel:components:ImageViewCreateInfo :: ComponentMapping $sel:format:ImageViewCreateInfo :: Format $sel:viewType:ImageViewCreateInfo :: ImageViewType $sel:image:ImageViewCreateInfo :: Image $sel:flags:ImageViewCreateInfo :: ImageViewCreateFlags ..} getNext :: forall (es :: [*]). ImageViewCreateInfo es -> Chain es getNext ImageViewCreateInfo{Chain es Format Image ImageSubresourceRange ComponentMapping ImageViewType ImageViewCreateFlags subresourceRange :: ImageSubresourceRange components :: ComponentMapping format :: Format viewType :: ImageViewType image :: Image flags :: ImageViewCreateFlags next :: Chain es $sel:subresourceRange:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageSubresourceRange $sel:components:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ComponentMapping $sel:format:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Format $sel:viewType:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewType $sel:image:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Image $sel:flags:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewCreateFlags $sel:next:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Chain es ..} = Chain es next extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageViewCreateInfo e => b) -> Maybe b extends :: forall e b (proxy :: * -> *). Typeable e => proxy e -> (Extends ImageViewCreateInfo e => b) -> Maybe b extends proxy e _ Extends ImageViewCreateInfo e => b f | Just e :~: ImageViewSampleWeightCreateInfoQCOM Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImageViewSampleWeightCreateInfoQCOM = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: ExportMetalObjectCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMetalObjectCreateInfoEXT = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: ImageViewMinLodCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImageViewMinLodCreateInfoEXT = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: OpaqueCaptureDescriptorDataCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @OpaqueCaptureDescriptorDataCreateInfoEXT = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: ImageViewASTCDecodeModeEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImageViewASTCDecodeModeEXT = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: SamplerYcbcrConversionInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @SamplerYcbcrConversionInfo = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: ImageViewSlicedCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImageViewSlicedCreateInfoEXT = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Just e :~: ImageViewUsageCreateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImageViewUsageCreateInfo = forall a. a -> Maybe a Just Extends ImageViewCreateInfo e => b f | Bool otherwise = forall a. Maybe a Nothing instance ( Extendss ImageViewCreateInfo es , PokeChain es ) => ToCStruct (ImageViewCreateInfo es) where withCStruct :: forall b. ImageViewCreateInfo es -> (Ptr (ImageViewCreateInfo es) -> IO b) -> IO b withCStruct ImageViewCreateInfo es x Ptr (ImageViewCreateInfo es) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 80 forall a b. (a -> b) -> a -> b $ \Ptr (ImageViewCreateInfo es) p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr (ImageViewCreateInfo es) p ImageViewCreateInfo es x (Ptr (ImageViewCreateInfo es) -> IO b f Ptr (ImageViewCreateInfo es) p) pokeCStruct :: forall b. Ptr (ImageViewCreateInfo es) -> ImageViewCreateInfo es -> IO b -> IO b pokeCStruct Ptr (ImageViewCreateInfo es) p ImageViewCreateInfo{Chain es Format Image ImageSubresourceRange ComponentMapping ImageViewType ImageViewCreateFlags subresourceRange :: ImageSubresourceRange components :: ComponentMapping format :: Format viewType :: ImageViewType image :: Image flags :: ImageViewCreateFlags next :: Chain es $sel:subresourceRange:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageSubresourceRange $sel:components:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ComponentMapping $sel:format:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Format $sel:viewType:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewType $sel:image:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Image $sel:flags:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> ImageViewCreateFlags $sel:next:ImageViewCreateInfo :: forall (es :: [*]). ImageViewCreateInfo es -> Chain es ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO) Ptr () pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . 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 (es :: [*]) a. PokeChain es => Chain es -> (Ptr (Chain es) -> IO a) -> IO a withChain (Chain es next) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext'' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr ImageViewCreateFlags)) (ImageViewCreateFlags flags) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Image)) (Image image) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageViewType)) (ImageViewType viewType) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 36 :: Ptr Format)) (Format format) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ComponentMapping)) (ComponentMapping components) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange subresourceRange) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 80 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr (ImageViewCreateInfo es) -> IO b -> IO b pokeZeroCStruct Ptr (ImageViewCreateInfo es) p IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO) Ptr () pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . 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 (es :: [*]) a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a withZeroChain @es forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Image)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageViewType)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 36 :: Ptr Format)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ComponentMapping)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr ImageSubresourceRange)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance ( Extendss ImageViewCreateInfo es , PeekChain es ) => FromCStruct (ImageViewCreateInfo es) where peekCStruct :: Ptr (ImageViewCreateInfo es) -> IO (ImageViewCreateInfo es) peekCStruct Ptr (ImageViewCreateInfo es) p = do Ptr () pNext <- forall a. Storable a => Ptr a -> IO a peek @(Ptr ()) ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Chain es next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es) peekChain (forall a b. Ptr a -> Ptr b castPtr Ptr () pNext) ImageViewCreateFlags flags <- forall a. Storable a => Ptr a -> IO a peek @ImageViewCreateFlags ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr ImageViewCreateFlags)) Image image <- forall a. Storable a => Ptr a -> IO a peek @Image ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Image)) ImageViewType viewType <- forall a. Storable a => Ptr a -> IO a peek @ImageViewType ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageViewType)) Format format <- forall a. Storable a => Ptr a -> IO a peek @Format ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 36 :: Ptr Format)) ComponentMapping components <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ComponentMapping ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr ComponentMapping)) ImageSubresourceRange subresourceRange <- forall a. FromCStruct a => Ptr a -> IO a peekCStruct @ImageSubresourceRange ((Ptr (ImageViewCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr ImageSubresourceRange)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall (es :: [*]). Chain es -> ImageViewCreateFlags -> Image -> ImageViewType -> Format -> ComponentMapping -> ImageSubresourceRange -> ImageViewCreateInfo es ImageViewCreateInfo Chain es next ImageViewCreateFlags flags Image image ImageViewType viewType Format format ComponentMapping components ImageSubresourceRange subresourceRange instance es ~ '[] => Zero (ImageViewCreateInfo es) where zero :: ImageViewCreateInfo es zero = forall (es :: [*]). Chain es -> ImageViewCreateFlags -> Image -> ImageViewType -> Format -> ComponentMapping -> ImageSubresourceRange -> ImageViewCreateInfo es ImageViewCreateInfo () forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero