{-# language CPP #-}
module Vulkan.Core10.ImageView ( createImageView
, withImageView
, destroyImageView
, ComponentMapping(..)
, ImageViewCreateInfo(..)
) 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 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.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.Dynamic (DeviceCmds(pVkCreateImageView))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyImageView))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.SharedTypes (ImageSubresourceRange)
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 Vulkan.Core10.Enums.ImageViewType (ImageViewType)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (ImageViewUsageCreateInfo)
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.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
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
createImageView :: forall a io
. (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io)
=>
Device
->
(ImageViewCreateInfo a)
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (ImageView)
createImageView :: Device
-> ImageViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ImageView
createImageView device :: Device
device createInfo :: ImageViewCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO ImageView -> io ImageView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageView -> io ImageView)
-> (ContT ImageView IO ImageView -> IO ImageView)
-> ContT ImageView IO ImageView
-> io ImageView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ImageView IO ImageView -> IO ImageView
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ImageView IO ImageView -> io ImageView)
-> ContT ImageView IO ImageView -> io ImageView
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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT ImageView IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageView IO ()) -> IO () -> ContT ImageView 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 ImageViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr ImageView)
-> IO Result)
vkCreateImageViewPtr FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr ImageView)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr ImageView)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr ImageView)
-> 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 vkCreateImageView is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((Ptr (ImageViewCreateInfo a) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO (Ptr (ImageViewCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageViewCreateInfo a) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO (Ptr (ImageViewCreateInfo a)))
-> ((Ptr (ImageViewCreateInfo a) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO (Ptr (ImageViewCreateInfo a))
forall a b. (a -> b) -> a -> b
$ ImageViewCreateInfo a
-> (Ptr (ImageViewCreateInfo a) -> IO ImageView) -> IO ImageView
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
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT ImageView 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 ImageView)
-> IO ImageView)
-> ContT ImageView 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 ImageView)
-> IO ImageView)
-> ContT ImageView IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ImageView)
-> IO ImageView)
-> ContT ImageView IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ImageView)
-> IO ImageView
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pView" ::: Ptr ImageView
pPView <- ((("pView" ::: Ptr ImageView) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO ("pView" ::: Ptr ImageView)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pView" ::: Ptr ImageView) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO ("pView" ::: Ptr ImageView))
-> ((("pView" ::: Ptr ImageView) -> IO ImageView) -> IO ImageView)
-> ContT ImageView IO ("pView" ::: Ptr ImageView)
forall a b. (a -> b) -> a -> b
$ IO ("pView" ::: Ptr ImageView)
-> (("pView" ::: Ptr ImageView) -> IO ())
-> (("pView" ::: Ptr ImageView) -> IO ImageView)
-> IO ImageView
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pView" ::: Ptr ImageView)
forall a. Int -> IO (Ptr a)
callocBytes @ImageView 8) ("pView" ::: Ptr ImageView) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ImageView IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ImageView IO Result)
-> IO Result -> ContT ImageView IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr ImageView)
-> IO Result
vkCreateImageView' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (ImageViewCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct ImageViewCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (ImageViewCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pView" ::: Ptr ImageView
pPView)
IO () -> ContT ImageView IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ImageView IO ()) -> IO () -> ContT ImageView 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))
ImageView
pView <- IO ImageView -> ContT ImageView IO ImageView
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ImageView -> ContT ImageView IO ImageView)
-> IO ImageView -> ContT ImageView IO ImageView
forall a b. (a -> b) -> a -> b
$ ("pView" ::: Ptr ImageView) -> IO ImageView
forall a. Storable a => Ptr a -> IO a
peek @ImageView "pView" ::: Ptr ImageView
pPView
ImageView -> ContT ImageView IO ImageView
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageView -> ContT ImageView IO ImageView)
-> ImageView -> ContT ImageView IO ImageView
forall a b. (a -> b) -> a -> b
$ (ImageView
pView)
withImageView :: forall a io r . (Extendss ImageViewCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageViewCreateInfo a -> Maybe AllocationCallbacks -> (io (ImageView) -> ((ImageView) -> io ()) -> r) -> r
withImageView :: Device
-> ImageViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io ImageView -> (ImageView -> io ()) -> r)
-> r
withImageView device :: Device
device pCreateInfo :: ImageViewCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io ImageView -> (ImageView -> io ()) -> r
b =
io ImageView -> (ImageView -> io ()) -> r
b (Device
-> ImageViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ImageView
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) -> Device
-> ImageView
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
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 ()
destroyImageView :: forall io
. (MonadIO io)
=>
Device
->
ImageView
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyImageView :: Device
-> ImageView
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyImageView device :: Device
device imageView :: ImageView
imageView 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 vkDestroyImageViewPtr :: FunPtr
(Ptr Device_T
-> ImageView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyImageViewPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ImageView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkDestroyImageView (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
-> ImageView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyImageViewPtr FunPtr
(Ptr Device_T
-> ImageView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> FunPtr
(Ptr Device_T
-> ImageView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ImageView
-> ("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 vkDestroyImageView is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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
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
-> ImageView -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyImageView' (Device -> Ptr Device_T
deviceHandle (Device
device)) (ImageView
imageView) "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
$ ()
data ComponentMapping = ComponentMapping
{
ComponentMapping -> ComponentSwizzle
r :: ComponentSwizzle
,
ComponentMapping -> ComponentSwizzle
g :: ComponentSwizzle
,
ComponentMapping -> ComponentSwizzle
b :: ComponentSwizzle
,
ComponentMapping -> ComponentSwizzle
a :: ComponentSwizzle
}
deriving (Typeable, ComponentMapping -> ComponentMapping -> Bool
(ComponentMapping -> ComponentMapping -> Bool)
-> (ComponentMapping -> ComponentMapping -> Bool)
-> Eq ComponentMapping
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 :: ComponentMapping -> (Ptr ComponentMapping -> IO b) -> IO b
withCStruct x :: ComponentMapping
x f :: Ptr ComponentMapping -> IO b
f = Int -> Int -> (Ptr ComponentMapping -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ComponentMapping -> IO b) -> IO b)
-> (Ptr ComponentMapping -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ComponentMapping
p -> Ptr ComponentMapping -> ComponentMapping -> IO b -> IO b
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 :: Ptr ComponentMapping -> ComponentMapping -> IO b -> IO b
pokeCStruct p :: Ptr ComponentMapping
p ComponentMapping{..} f :: IO b
f = do
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ComponentSwizzle)) (ComponentSwizzle
r)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ComponentSwizzle)) (ComponentSwizzle
g)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr ComponentSwizzle)) (ComponentSwizzle
b)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr ComponentSwizzle)) (ComponentSwizzle
a)
IO b
f
cStructSize :: Int
cStructSize = 16
cStructAlignment :: Int
cStructAlignment = 4
pokeZeroCStruct :: Ptr ComponentMapping -> IO b -> IO b
pokeZeroCStruct p :: Ptr ComponentMapping
p f :: IO b
f = do
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ComponentSwizzle)) (ComponentSwizzle
forall a. Zero a => a
zero)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ComponentSwizzle)) (ComponentSwizzle
forall a. Zero a => a
zero)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr ComponentSwizzle)) (ComponentSwizzle
forall a. Zero a => a
zero)
Ptr ComponentSwizzle -> ComponentSwizzle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr ComponentSwizzle)) (ComponentSwizzle
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ComponentMapping where
peekCStruct :: Ptr ComponentMapping -> IO ComponentMapping
peekCStruct p :: Ptr ComponentMapping
p = do
ComponentSwizzle
r <- Ptr ComponentSwizzle -> IO ComponentSwizzle
forall a. Storable a => Ptr a -> IO a
peek @ComponentSwizzle ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ComponentSwizzle))
ComponentSwizzle
g <- Ptr ComponentSwizzle -> IO ComponentSwizzle
forall a. Storable a => Ptr a -> IO a
peek @ComponentSwizzle ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ComponentSwizzle))
ComponentSwizzle
b <- Ptr ComponentSwizzle -> IO ComponentSwizzle
forall a. Storable a => Ptr a -> IO a
peek @ComponentSwizzle ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr ComponentSwizzle))
ComponentSwizzle
a <- Ptr ComponentSwizzle -> IO ComponentSwizzle
forall a. Storable a => Ptr a -> IO a
peek @ComponentSwizzle ((Ptr ComponentMapping
p Ptr ComponentMapping -> Int -> Ptr ComponentSwizzle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr ComponentSwizzle))
ComponentMapping -> IO ComponentMapping
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ComponentMapping -> IO ComponentMapping)
-> ComponentMapping -> IO ComponentMapping
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
_ = 16
alignment :: ComponentMapping -> Int
alignment ~ComponentMapping
_ = 4
peek :: Ptr ComponentMapping -> IO ComponentMapping
peek = Ptr ComponentMapping -> IO ComponentMapping
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ComponentMapping -> ComponentMapping -> IO ()
poke ptr :: Ptr ComponentMapping
ptr poked :: ComponentMapping
poked = Ptr ComponentMapping -> ComponentMapping -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ComponentMapping
ptr ComponentMapping
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ComponentMapping where
zero :: ComponentMapping
zero = ComponentSwizzle
-> ComponentSwizzle
-> ComponentSwizzle
-> ComponentSwizzle
-> ComponentMapping
ComponentMapping
ComponentSwizzle
forall a. Zero a => a
zero
ComponentSwizzle
forall a. Zero a => a
zero
ComponentSwizzle
forall a. Zero a => a
zero
ComponentSwizzle
forall a. Zero a => a
zero
data ImageViewCreateInfo (es :: [Type]) = ImageViewCreateInfo
{
ImageViewCreateInfo es -> Chain es
next :: Chain es
,
ImageViewCreateInfo es -> ImageViewCreateFlags
flags :: ImageViewCreateFlags
,
ImageViewCreateInfo es -> Image
image :: Image
,
ImageViewCreateInfo es -> ImageViewType
viewType :: ImageViewType
,
ImageViewCreateInfo es -> Format
format :: Format
,
ImageViewCreateInfo es -> ComponentMapping
components :: ComponentMapping
,
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
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO
setNext :: ImageViewCreateInfo ds -> Chain es -> ImageViewCreateInfo es
setNext x :: ImageViewCreateInfo ds
x next :: Chain es
next = ImageViewCreateInfo ds
x{$sel:next:ImageViewCreateInfo :: Chain es
next = Chain es
next}
getNext :: ImageViewCreateInfo es -> Chain es
getNext ImageViewCreateInfo{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageViewCreateInfo e => b) -> Maybe b
extends :: proxy e -> (Extends ImageViewCreateInfo e => b) -> Maybe b
extends _ f :: Extends ImageViewCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageViewASTCDecodeModeEXT) =>
Maybe (e :~: ImageViewASTCDecodeModeEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageViewASTCDecodeModeEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageViewCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable SamplerYcbcrConversionInfo) =>
Maybe (e :~: SamplerYcbcrConversionInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SamplerYcbcrConversionInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageViewCreateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImageViewUsageCreateInfo) =>
Maybe (e :~: ImageViewUsageCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageViewUsageCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageViewCreateInfo e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss ImageViewCreateInfo es, PokeChain es) => ToCStruct (ImageViewCreateInfo es) where
withCStruct :: ImageViewCreateInfo es
-> (Ptr (ImageViewCreateInfo es) -> IO b) -> IO b
withCStruct x :: ImageViewCreateInfo es
x f :: Ptr (ImageViewCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (ImageViewCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 8 ((Ptr (ImageViewCreateInfo es) -> IO b) -> IO b)
-> (Ptr (ImageViewCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (ImageViewCreateInfo es)
p -> Ptr (ImageViewCreateInfo es)
-> ImageViewCreateInfo es -> IO b -> IO b
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 :: Ptr (ImageViewCreateInfo es)
-> ImageViewCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (ImageViewCreateInfo es)
p ImageViewCreateInfo{..} 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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo 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 ImageViewCreateFlags -> ImageViewCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageViewCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageViewCreateFlags)) (ImageViewCreateFlags
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 Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Image)) (Image
image)
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 ImageViewType -> ImageViewType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageViewType)) (ImageViewType
viewType)
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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: 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 ComponentMapping -> ComponentMapping -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentMapping)) (ComponentMapping
components) (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 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 ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
subresourceRange) (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 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 = 80
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (ImageViewCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (ImageViewCreateInfo 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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo 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 Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Image)) (Image
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 ImageViewType -> ImageViewType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageViewType)) (ImageViewType
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 (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: 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 ComponentMapping -> ComponentMapping -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentMapping)) (ComponentMapping
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 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 ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
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 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 ImageViewCreateInfo es, PeekChain es) => FromCStruct (ImageViewCreateInfo es) where
peekCStruct :: Ptr (ImageViewCreateInfo es) -> IO (ImageViewCreateInfo es)
peekCStruct p :: Ptr (ImageViewCreateInfo es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo 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)
ImageViewCreateFlags
flags <- Ptr ImageViewCreateFlags -> IO ImageViewCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageViewCreateFlags ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageViewCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageViewCreateFlags))
Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Image))
ImageViewType
viewType <- Ptr ImageViewType -> IO ImageViewType
forall a. Storable a => Ptr a -> IO a
peek @ImageViewType ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageViewType))
Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Format))
ComponentMapping
components <- Ptr ComponentMapping -> IO ComponentMapping
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ComponentMapping ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentMapping))
ImageSubresourceRange
subresourceRange <- Ptr ImageSubresourceRange -> IO ImageSubresourceRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceRange ((Ptr (ImageViewCreateInfo es)
p Ptr (ImageViewCreateInfo es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageSubresourceRange))
ImageViewCreateInfo es -> IO (ImageViewCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewCreateInfo es -> IO (ImageViewCreateInfo es))
-> ImageViewCreateInfo es -> IO (ImageViewCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> ImageViewCreateFlags
-> Image
-> ImageViewType
-> Format
-> ComponentMapping
-> ImageSubresourceRange
-> ImageViewCreateInfo es
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 = Chain es
-> ImageViewCreateFlags
-> Image
-> ImageViewType
-> Format
-> ComponentMapping
-> ImageSubresourceRange
-> ImageViewCreateInfo es
forall (es :: [*]).
Chain es
-> ImageViewCreateFlags
-> Image
-> ImageViewType
-> Format
-> ComponentMapping
-> ImageSubresourceRange
-> ImageViewCreateInfo es
ImageViewCreateInfo
()
ImageViewCreateFlags
forall a. Zero a => a
zero
Image
forall a. Zero a => a
zero
ImageViewType
forall a. Zero a => a
zero
Format
forall a. Zero a => a
zero
ComponentMapping
forall a. Zero a => a
zero
ImageSubresourceRange
forall a. Zero a => a
zero