{-# language CPP #-}
module Vulkan.Core10.Image ( createImage
, withImage
, destroyImage
, getImageSubresourceLayout
, ImageSubresource(..)
, ImageCreateInfo(..)
, SubresourceLayout(..)
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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 Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.CStruct.Extends (Chain)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_dedicated_allocation (DedicatedAllocationImageCreateInfoNV)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCreateImage))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyImage))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageSubresourceLayout))
import Vulkan.Core10.BaseType (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.SharedTypes (Extent3D)
import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer (ExternalFormatANDROID)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory (ExternalMemoryImageCreateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory (ExternalMemoryImageCreateInfoNV)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_drm_format_modifier (ImageDrmFormatModifierExplicitCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_drm_format_modifier (ImageDrmFormatModifierListCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_image_format_list (ImageFormatListCreateInfo)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage (ImageStencilUsageCreateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_swapchain (ImageSwapchainCreateInfoKHR)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling)
import Vulkan.Core10.Enums.ImageType (ImageType)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
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 Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SharingMode (SharingMode)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateImage
:: FunPtr (Ptr Device_T -> Ptr (SomeStruct ImageCreateInfo) -> Ptr AllocationCallbacks -> Ptr Image -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct ImageCreateInfo) -> Ptr AllocationCallbacks -> Ptr Image -> IO Result
createImage :: forall a io
. (Extendss ImageCreateInfo a, PokeChain a, MonadIO io)
=>
Device
->
(ImageCreateInfo a)
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (Image)
createImage :: Device
-> ImageCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Image
createImage device :: Device
device createInfo :: ImageCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Image -> io Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> io Image)
-> (ContT Image IO Image -> IO Image)
-> ContT Image IO Image
-> io Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Image IO Image -> IO Image
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Image IO Image -> io Image)
-> ContT Image IO Image -> io Image
forall a b. (a -> b) -> a -> b
$ do
let vkCreateImagePtr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
vkCreateImagePtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
pVkCreateImage (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT Image IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Image IO ()) -> IO () -> ContT Image IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
vkCreateImagePtr FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCreateImage' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result
vkCreateImage' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result
mkVkCreateImage FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result)
vkCreateImagePtr
Ptr (ImageCreateInfo a)
pCreateInfo <- ((Ptr (ImageCreateInfo a) -> IO Image) -> IO Image)
-> ContT Image IO (Ptr (ImageCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageCreateInfo a) -> IO Image) -> IO Image)
-> ContT Image IO (Ptr (ImageCreateInfo a)))
-> ((Ptr (ImageCreateInfo a) -> IO Image) -> IO Image)
-> ContT Image IO (Ptr (ImageCreateInfo a))
forall a b. (a -> b) -> a -> b
$ ImageCreateInfo a
-> (Ptr (ImageCreateInfo a) -> IO Image) -> IO Image
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageCreateInfo a
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Image IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Image)
-> IO Image)
-> ContT Image IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Image)
-> IO Image)
-> ContT Image IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Image)
-> IO Image)
-> ContT Image IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Image)
-> IO Image
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pImage" ::: Ptr Image
pPImage <- ((("pImage" ::: Ptr Image) -> IO Image) -> IO Image)
-> ContT Image IO ("pImage" ::: Ptr Image)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pImage" ::: Ptr Image) -> IO Image) -> IO Image)
-> ContT Image IO ("pImage" ::: Ptr Image))
-> ((("pImage" ::: Ptr Image) -> IO Image) -> IO Image)
-> ContT Image IO ("pImage" ::: Ptr Image)
forall a b. (a -> b) -> a -> b
$ IO ("pImage" ::: Ptr Image)
-> (("pImage" ::: Ptr Image) -> IO ())
-> (("pImage" ::: Ptr Image) -> IO Image)
-> IO Image
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pImage" ::: Ptr Image)
forall a. Int -> IO (Ptr a)
callocBytes @Image 8) ("pImage" ::: Ptr Image) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT Image IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Image IO Result)
-> IO Result -> ContT Image IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pImage" ::: Ptr Image)
-> IO Result
vkCreateImage' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (ImageCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (ImageCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pImage" ::: Ptr Image
pPImage)
IO () -> ContT Image IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Image IO ()) -> IO () -> ContT Image IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Image
pImage <- IO Image -> ContT Image IO Image
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Image -> ContT Image IO Image)
-> IO Image -> ContT Image IO Image
forall a b. (a -> b) -> a -> b
$ ("pImage" ::: Ptr Image) -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image "pImage" ::: Ptr Image
pPImage
Image -> ContT Image IO Image
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Image -> ContT Image IO Image) -> Image -> ContT Image IO Image
forall a b. (a -> b) -> a -> b
$ (Image
pImage)
withImage :: forall a io r . (Extendss ImageCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageCreateInfo a -> Maybe AllocationCallbacks -> (io (Image) -> ((Image) -> io ()) -> r) -> r
withImage :: Device
-> ImageCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Image -> (Image -> io ()) -> r)
-> r
withImage device :: Device
device pCreateInfo :: ImageCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io Image -> (Image -> io ()) -> r
b =
io Image -> (Image -> io ()) -> r
b (Device
-> ImageCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Image
forall (a :: [*]) (io :: * -> *).
(Extendss ImageCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> ImageCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Image
createImage Device
device ImageCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(Image
o0) -> Device
-> Image -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Image -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyImage Device
device Image
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkDestroyImage
:: FunPtr (Ptr Device_T -> Image -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> Image -> Ptr AllocationCallbacks -> IO ()
destroyImage :: forall io
. (MonadIO io)
=>
Device
->
Image
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyImage :: Device
-> Image -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyImage device :: Device
device image :: Image
image allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkDestroyImagePtr :: FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyImagePtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyImage (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyImagePtr FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyImage is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkDestroyImage' :: Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyImage' = FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Device_T
-> Image
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyImage FunPtr
(Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyImagePtr
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyImage' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Image
image) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetImageSubresourceLayout
:: FunPtr (Ptr Device_T -> Image -> Ptr ImageSubresource -> Ptr SubresourceLayout -> IO ()) -> Ptr Device_T -> Image -> Ptr ImageSubresource -> Ptr SubresourceLayout -> IO ()
getImageSubresourceLayout :: forall io
. (MonadIO io)
=>
Device
->
Image
->
ImageSubresource
-> io (SubresourceLayout)
getImageSubresourceLayout :: Device -> Image -> ImageSubresource -> io SubresourceLayout
getImageSubresourceLayout device :: Device
device image :: Image
image subresource :: ImageSubresource
subresource = IO SubresourceLayout -> io SubresourceLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SubresourceLayout -> io SubresourceLayout)
-> (ContT SubresourceLayout IO SubresourceLayout
-> IO SubresourceLayout)
-> ContT SubresourceLayout IO SubresourceLayout
-> io SubresourceLayout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT SubresourceLayout IO SubresourceLayout
-> IO SubresourceLayout
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT SubresourceLayout IO SubresourceLayout
-> io SubresourceLayout)
-> ContT SubresourceLayout IO SubresourceLayout
-> io SubresourceLayout
forall a b. (a -> b) -> a -> b
$ do
let vkGetImageSubresourceLayoutPtr :: FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
vkGetImageSubresourceLayoutPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
pVkGetImageSubresourceLayout (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT SubresourceLayout IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SubresourceLayout IO ())
-> IO () -> ContT SubresourceLayout IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
vkGetImageSubresourceLayoutPtr FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
-> FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetImageSubresourceLayout is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetImageSubresourceLayout' :: Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ()
vkGetImageSubresourceLayout' = FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
-> Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ()
mkVkGetImageSubresourceLayout FunPtr
(Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ())
vkGetImageSubresourceLayoutPtr
"pSubresource" ::: Ptr ImageSubresource
pSubresource <- ((("pSubresource" ::: Ptr ImageSubresource)
-> IO SubresourceLayout)
-> IO SubresourceLayout)
-> ContT
SubresourceLayout IO ("pSubresource" ::: Ptr ImageSubresource)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubresource" ::: Ptr ImageSubresource)
-> IO SubresourceLayout)
-> IO SubresourceLayout)
-> ContT
SubresourceLayout IO ("pSubresource" ::: Ptr ImageSubresource))
-> ((("pSubresource" ::: Ptr ImageSubresource)
-> IO SubresourceLayout)
-> IO SubresourceLayout)
-> ContT
SubresourceLayout IO ("pSubresource" ::: Ptr ImageSubresource)
forall a b. (a -> b) -> a -> b
$ ImageSubresource
-> (("pSubresource" ::: Ptr ImageSubresource)
-> IO SubresourceLayout)
-> IO SubresourceLayout
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageSubresource
subresource)
"pLayout" ::: Ptr SubresourceLayout
pPLayout <- ((("pLayout" ::: Ptr SubresourceLayout) -> IO SubresourceLayout)
-> IO SubresourceLayout)
-> ContT SubresourceLayout IO ("pLayout" ::: Ptr SubresourceLayout)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct SubresourceLayout =>
(("pLayout" ::: Ptr SubresourceLayout) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @SubresourceLayout)
IO () -> ContT SubresourceLayout IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SubresourceLayout IO ())
-> IO () -> ContT SubresourceLayout IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Image
-> ("pSubresource" ::: Ptr ImageSubresource)
-> ("pLayout" ::: Ptr SubresourceLayout)
-> IO ()
vkGetImageSubresourceLayout' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Image
image) "pSubresource" ::: Ptr ImageSubresource
pSubresource ("pLayout" ::: Ptr SubresourceLayout
pPLayout)
SubresourceLayout
pLayout <- IO SubresourceLayout
-> ContT SubresourceLayout IO SubresourceLayout
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO SubresourceLayout
-> ContT SubresourceLayout IO SubresourceLayout)
-> IO SubresourceLayout
-> ContT SubresourceLayout IO SubresourceLayout
forall a b. (a -> b) -> a -> b
$ ("pLayout" ::: Ptr SubresourceLayout) -> IO SubresourceLayout
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubresourceLayout "pLayout" ::: Ptr SubresourceLayout
pPLayout
SubresourceLayout -> ContT SubresourceLayout IO SubresourceLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubresourceLayout -> ContT SubresourceLayout IO SubresourceLayout)
-> SubresourceLayout
-> ContT SubresourceLayout IO SubresourceLayout
forall a b. (a -> b) -> a -> b
$ (SubresourceLayout
pLayout)
data ImageSubresource = ImageSubresource
{
ImageSubresource -> ImageAspectFlags
aspectMask :: ImageAspectFlags
,
ImageSubresource -> Word32
mipLevel :: Word32
,
ImageSubresource -> Word32
arrayLayer :: Word32
}
deriving (Typeable, ImageSubresource -> ImageSubresource -> Bool
(ImageSubresource -> ImageSubresource -> Bool)
-> (ImageSubresource -> ImageSubresource -> Bool)
-> Eq ImageSubresource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSubresource -> ImageSubresource -> Bool
$c/= :: ImageSubresource -> ImageSubresource -> Bool
== :: ImageSubresource -> ImageSubresource -> Bool
$c== :: ImageSubresource -> ImageSubresource -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageSubresource)
#endif
deriving instance Show ImageSubresource
instance ToCStruct ImageSubresource where
withCStruct :: ImageSubresource
-> (("pSubresource" ::: Ptr ImageSubresource) -> IO b) -> IO b
withCStruct x :: ImageSubresource
x f :: ("pSubresource" ::: Ptr ImageSubresource) -> IO b
f = Int
-> Int
-> (("pSubresource" ::: Ptr ImageSubresource) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((("pSubresource" ::: Ptr ImageSubresource) -> IO b) -> IO b)
-> (("pSubresource" ::: Ptr ImageSubresource) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSubresource" ::: Ptr ImageSubresource
p -> ("pSubresource" ::: Ptr ImageSubresource)
-> ImageSubresource -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubresource" ::: Ptr ImageSubresource
p ImageSubresource
x (("pSubresource" ::: Ptr ImageSubresource) -> IO b
f "pSubresource" ::: Ptr ImageSubresource
p)
pokeCStruct :: ("pSubresource" ::: Ptr ImageSubresource)
-> ImageSubresource -> IO b -> IO b
pokeCStruct p :: "pSubresource" ::: Ptr ImageSubresource
p ImageSubresource{..} f :: IO b
f = do
Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
mipLevel)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
arrayLayer)
IO b
f
cStructSize :: Int
cStructSize = 12
cStructAlignment :: Int
cStructAlignment = 4
pokeZeroCStruct :: ("pSubresource" ::: Ptr ImageSubresource) -> IO b -> IO b
pokeZeroCStruct p :: "pSubresource" ::: Ptr ImageSubresource
p f :: IO b
f = do
Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageSubresource where
peekCStruct :: ("pSubresource" ::: Ptr ImageSubresource) -> IO ImageSubresource
peekCStruct p :: "pSubresource" ::: Ptr ImageSubresource
p = do
ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource)
-> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags))
Word32
mipLevel <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
Word32
arrayLayer <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSubresource" ::: Ptr ImageSubresource
p ("pSubresource" ::: Ptr ImageSubresource) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
ImageSubresource -> IO ImageSubresource
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageSubresource -> IO ImageSubresource)
-> ImageSubresource -> IO ImageSubresource
forall a b. (a -> b) -> a -> b
$ ImageAspectFlags -> Word32 -> Word32 -> ImageSubresource
ImageSubresource
ImageAspectFlags
aspectMask Word32
mipLevel Word32
arrayLayer
instance Storable ImageSubresource where
sizeOf :: ImageSubresource -> Int
sizeOf ~ImageSubresource
_ = 12
alignment :: ImageSubresource -> Int
alignment ~ImageSubresource
_ = 4
peek :: ("pSubresource" ::: Ptr ImageSubresource) -> IO ImageSubresource
peek = ("pSubresource" ::: Ptr ImageSubresource) -> IO ImageSubresource
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pSubresource" ::: Ptr ImageSubresource)
-> ImageSubresource -> IO ()
poke ptr :: "pSubresource" ::: Ptr ImageSubresource
ptr poked :: ImageSubresource
poked = ("pSubresource" ::: Ptr ImageSubresource)
-> ImageSubresource -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubresource" ::: Ptr ImageSubresource
ptr ImageSubresource
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageSubresource where
zero :: ImageSubresource
zero = ImageAspectFlags -> Word32 -> Word32 -> ImageSubresource
ImageSubresource
ImageAspectFlags
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
data ImageCreateInfo (es :: [Type]) = ImageCreateInfo
{
ImageCreateInfo es -> Chain es
next :: Chain es
,
ImageCreateInfo es -> ImageCreateFlags
flags :: ImageCreateFlags
,
ImageCreateInfo es -> ImageType
imageType :: ImageType
,
ImageCreateInfo es -> Format
format :: Format
,
ImageCreateInfo es -> Extent3D
extent :: Extent3D
,
ImageCreateInfo es -> Word32
mipLevels :: Word32
,
ImageCreateInfo es -> Word32
arrayLayers :: Word32
,
ImageCreateInfo es -> SampleCountFlagBits
samples :: SampleCountFlagBits
,
ImageCreateInfo es -> ImageTiling
tiling :: ImageTiling
,
ImageCreateInfo es -> ImageUsageFlags
usage :: ImageUsageFlags
,
ImageCreateInfo es -> SharingMode
sharingMode :: SharingMode
,
ImageCreateInfo es -> Vector Word32
queueFamilyIndices :: Vector Word32
,
ImageCreateInfo es -> ImageLayout
initialLayout :: ImageLayout
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (ImageCreateInfo es)
instance Extensible ImageCreateInfo where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_IMAGE_CREATE_INFO
setNext :: ImageCreateInfo ds -> Chain es -> ImageCreateInfo es
setNext x :: ImageCreateInfo ds
x next :: Chain es
next = ImageCreateInfo ds
x{$sel:next:ImageCreateInfo :: Chain es
next = Chain es
next}
getNext :: ImageCreateInfo es -> Chain es
getNext ImageCreateInfo{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageCreateInfo e => b) -> Maybe b
extends :: proxy e -> (Extends ImageCreateInfo e => b) -> Maybe b
extends _ f :: Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageStencilUsageCreateInfo) =>
Maybe (e :~: ImageStencilUsageCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageStencilUsageCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e,
Typeable ImageDrmFormatModifierExplicitCreateInfoEXT) =>
Maybe (e :~: ImageDrmFormatModifierExplicitCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageDrmFormatModifierExplicitCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageDrmFormatModifierListCreateInfoEXT) =>
Maybe (e :~: ImageDrmFormatModifierListCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageDrmFormatModifierListCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExternalFormatANDROID) =>
Maybe (e :~: ExternalFormatANDROID)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExternalFormatANDROID = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageFormatListCreateInfo) =>
Maybe (e :~: ImageFormatListCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageFormatListCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageSwapchainCreateInfoKHR) =>
Maybe (e :~: ImageSwapchainCreateInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageSwapchainCreateInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExternalMemoryImageCreateInfo) =>
Maybe (e :~: ExternalMemoryImageCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExternalMemoryImageCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExternalMemoryImageCreateInfoNV) =>
Maybe (e :~: ExternalMemoryImageCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExternalMemoryImageCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable DedicatedAllocationImageCreateInfoNV) =>
Maybe (e :~: DedicatedAllocationImageCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DedicatedAllocationImageCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageCreateInfo e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss ImageCreateInfo es, PokeChain es) => ToCStruct (ImageCreateInfo es) where
withCStruct :: ImageCreateInfo es -> (Ptr (ImageCreateInfo es) -> IO b) -> IO b
withCStruct x :: ImageCreateInfo es
x f :: Ptr (ImageCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (ImageCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 88 8 ((Ptr (ImageCreateInfo es) -> IO b) -> IO b)
-> (Ptr (ImageCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (ImageCreateInfo es)
p -> Ptr (ImageCreateInfo es) -> ImageCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (ImageCreateInfo es)
p ImageCreateInfo es
x (Ptr (ImageCreateInfo es) -> IO b
f Ptr (ImageCreateInfo es)
p)
pokeCStruct :: Ptr (ImageCreateInfo es) -> ImageCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (ImageCreateInfo es)
p ImageCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_CREATE_INFO)
Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageCreateFlags -> ImageCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageCreateFlags)) (ImageCreateFlags
flags)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
imageType)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Format)) (Format
format)
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Extent3D)) (Extent3D
extent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
mipLevels)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
arrayLayers)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
samples)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr ImageTiling)) (ImageTiling
tiling)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags)) (ImageUsageFlags
usage)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SharingMode -> SharingMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode)) (SharingMode
sharingMode)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
queueFamilyIndices)) :: Word32))
Ptr Word32
pPQueueFamilyIndices' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
queueFamilyIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPQueueFamilyIndices' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
queueFamilyIndices)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPQueueFamilyIndices')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr ImageLayout)) (ImageLayout
initialLayout)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 88
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (ImageCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (ImageCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_CREATE_INFO)
Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Extent3D)) (Extent3D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr ImageTiling)) (ImageTiling
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags)) (ImageUsageFlags
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SharingMode -> SharingMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode)) (SharingMode
forall a. Zero a => a
zero)
Ptr Word32
pPQueueFamilyIndices' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPQueueFamilyIndices' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPQueueFamilyIndices')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance (Extendss ImageCreateInfo es, PeekChain es) => FromCStruct (ImageCreateInfo es) where
peekCStruct :: Ptr (ImageCreateInfo es) -> IO (ImageCreateInfo es)
peekCStruct p :: Ptr (ImageCreateInfo es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
ImageCreateFlags
flags <- Ptr ImageCreateFlags -> IO ImageCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageCreateFlags ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageCreateFlags))
ImageType
imageType <- Ptr ImageType -> IO ImageType
forall a. Storable a => Ptr a -> IO a
peek @ImageType ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType))
Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Format))
Extent3D
extent <- Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Extent3D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Extent3D))
Word32
mipLevels <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
Word32
arrayLayers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32))
SampleCountFlagBits
samples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr SampleCountFlagBits))
ImageTiling
tiling <- Ptr ImageTiling -> IO ImageTiling
forall a. Storable a => Ptr a -> IO a
peek @ImageTiling ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr ImageTiling))
ImageUsageFlags
usage <- Ptr ImageUsageFlags -> IO ImageUsageFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags))
SharingMode
sharingMode <- Ptr SharingMode -> IO SharingMode
forall a. Storable a => Ptr a -> IO a
peek @SharingMode ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode))
Word32
queueFamilyIndexCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
Ptr Word32
pQueueFamilyIndices <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32)))
Vector Word32
pQueueFamilyIndices' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
queueFamilyIndexCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pQueueFamilyIndices Ptr Word32 -> Int -> Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
ImageLayout
initialLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (ImageCreateInfo es)
p Ptr (ImageCreateInfo es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr ImageLayout))
ImageCreateInfo es -> IO (ImageCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageCreateInfo es -> IO (ImageCreateInfo es))
-> ImageCreateInfo es -> IO (ImageCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> ImageCreateFlags
-> ImageType
-> Format
-> Extent3D
-> Word32
-> Word32
-> SampleCountFlagBits
-> ImageTiling
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> ImageLayout
-> ImageCreateInfo es
forall (es :: [*]).
Chain es
-> ImageCreateFlags
-> ImageType
-> Format
-> Extent3D
-> Word32
-> Word32
-> SampleCountFlagBits
-> ImageTiling
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> ImageLayout
-> ImageCreateInfo es
ImageCreateInfo
Chain es
next ImageCreateFlags
flags ImageType
imageType Format
format Extent3D
extent Word32
mipLevels Word32
arrayLayers SampleCountFlagBits
samples ImageTiling
tiling ImageUsageFlags
usage SharingMode
sharingMode Vector Word32
pQueueFamilyIndices' ImageLayout
initialLayout
instance es ~ '[] => Zero (ImageCreateInfo es) where
zero :: ImageCreateInfo es
zero = Chain es
-> ImageCreateFlags
-> ImageType
-> Format
-> Extent3D
-> Word32
-> Word32
-> SampleCountFlagBits
-> ImageTiling
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> ImageLayout
-> ImageCreateInfo es
forall (es :: [*]).
Chain es
-> ImageCreateFlags
-> ImageType
-> Format
-> Extent3D
-> Word32
-> Word32
-> SampleCountFlagBits
-> ImageTiling
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> ImageLayout
-> ImageCreateInfo es
ImageCreateInfo
()
ImageCreateFlags
forall a. Zero a => a
zero
ImageType
forall a. Zero a => a
zero
Format
forall a. Zero a => a
zero
Extent3D
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
SampleCountFlagBits
forall a. Zero a => a
zero
ImageTiling
forall a. Zero a => a
zero
ImageUsageFlags
forall a. Zero a => a
zero
SharingMode
forall a. Zero a => a
zero
Vector Word32
forall a. Monoid a => a
mempty
ImageLayout
forall a. Zero a => a
zero
data SubresourceLayout = SubresourceLayout
{
SubresourceLayout -> DeviceSize
offset :: DeviceSize
,
SubresourceLayout -> DeviceSize
size :: DeviceSize
,
SubresourceLayout -> DeviceSize
rowPitch :: DeviceSize
,
SubresourceLayout -> DeviceSize
arrayPitch :: DeviceSize
,
SubresourceLayout -> DeviceSize
depthPitch :: DeviceSize
}
deriving (Typeable, SubresourceLayout -> SubresourceLayout -> Bool
(SubresourceLayout -> SubresourceLayout -> Bool)
-> (SubresourceLayout -> SubresourceLayout -> Bool)
-> Eq SubresourceLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubresourceLayout -> SubresourceLayout -> Bool
$c/= :: SubresourceLayout -> SubresourceLayout -> Bool
== :: SubresourceLayout -> SubresourceLayout -> Bool
$c== :: SubresourceLayout -> SubresourceLayout -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubresourceLayout)
#endif
deriving instance Show SubresourceLayout
instance ToCStruct SubresourceLayout where
withCStruct :: SubresourceLayout
-> (("pLayout" ::: Ptr SubresourceLayout) -> IO b) -> IO b
withCStruct x :: SubresourceLayout
x f :: ("pLayout" ::: Ptr SubresourceLayout) -> IO b
f = Int
-> Int -> (("pLayout" ::: Ptr SubresourceLayout) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pLayout" ::: Ptr SubresourceLayout) -> IO b) -> IO b)
-> (("pLayout" ::: Ptr SubresourceLayout) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pLayout" ::: Ptr SubresourceLayout
p -> ("pLayout" ::: Ptr SubresourceLayout)
-> SubresourceLayout -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLayout" ::: Ptr SubresourceLayout
p SubresourceLayout
x (("pLayout" ::: Ptr SubresourceLayout) -> IO b
f "pLayout" ::: Ptr SubresourceLayout
p)
pokeCStruct :: ("pLayout" ::: Ptr SubresourceLayout)
-> SubresourceLayout -> IO b -> IO b
pokeCStruct p :: "pLayout" ::: Ptr SubresourceLayout
p SubresourceLayout{..} f :: IO b
f = do
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
offset)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) (DeviceSize
size)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
rowPitch)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
arrayPitch)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
depthPitch)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pLayout" ::: Ptr SubresourceLayout) -> IO b -> IO b
pokeZeroCStruct p :: "pLayout" ::: Ptr SubresourceLayout
p f :: IO b
f = do
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SubresourceLayout where
peekCStruct :: ("pLayout" ::: Ptr SubresourceLayout) -> IO SubresourceLayout
peekCStruct p :: "pLayout" ::: Ptr SubresourceLayout
p = do
DeviceSize
offset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
DeviceSize
size <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
DeviceSize
rowPitch <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
DeviceSize
arrayPitch <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
DeviceSize
depthPitch <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pLayout" ::: Ptr SubresourceLayout
p ("pLayout" ::: Ptr SubresourceLayout) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
SubresourceLayout -> IO SubresourceLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubresourceLayout -> IO SubresourceLayout)
-> SubresourceLayout -> IO SubresourceLayout
forall a b. (a -> b) -> a -> b
$ DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> SubresourceLayout
SubresourceLayout
DeviceSize
offset DeviceSize
size DeviceSize
rowPitch DeviceSize
arrayPitch DeviceSize
depthPitch
instance Storable SubresourceLayout where
sizeOf :: SubresourceLayout -> Int
sizeOf ~SubresourceLayout
_ = 40
alignment :: SubresourceLayout -> Int
alignment ~SubresourceLayout
_ = 8
peek :: ("pLayout" ::: Ptr SubresourceLayout) -> IO SubresourceLayout
peek = ("pLayout" ::: Ptr SubresourceLayout) -> IO SubresourceLayout
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pLayout" ::: Ptr SubresourceLayout) -> SubresourceLayout -> IO ()
poke ptr :: "pLayout" ::: Ptr SubresourceLayout
ptr poked :: SubresourceLayout
poked = ("pLayout" ::: Ptr SubresourceLayout)
-> SubresourceLayout -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLayout" ::: Ptr SubresourceLayout
ptr SubresourceLayout
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SubresourceLayout where
zero :: SubresourceLayout
zero = DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> DeviceSize
-> SubresourceLayout
SubresourceLayout
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero