{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer ( PhysicalDeviceImagelessFramebufferFeatures(..)
, FramebufferAttachmentsCreateInfo(..)
, FramebufferAttachmentImageInfo(..)
, RenderPassAttachmentBeginInfo(..)
, StructureType(..)
, FramebufferCreateFlagBits(..)
, FramebufferCreateFlags
) where
import Foreign.Marshal.Alloc (allocaBytes)
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 Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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 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.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core10.Handles (ImageView)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENTS_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENT_IMAGE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGELESS_FRAMEBUFFER_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_ATTACHMENT_BEGIN_INFO))
import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlagBits(..))
import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
data PhysicalDeviceImagelessFramebufferFeatures = PhysicalDeviceImagelessFramebufferFeatures
{
PhysicalDeviceImagelessFramebufferFeatures -> Bool
imagelessFramebuffer :: Bool }
deriving (Typeable, PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> Bool
$c/= :: PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> Bool
== :: PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> Bool
$c== :: PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImagelessFramebufferFeatures)
#endif
deriving instance Show PhysicalDeviceImagelessFramebufferFeatures
instance ToCStruct PhysicalDeviceImagelessFramebufferFeatures where
withCStruct :: forall b.
PhysicalDeviceImagelessFramebufferFeatures
-> (Ptr PhysicalDeviceImagelessFramebufferFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceImagelessFramebufferFeatures
x Ptr PhysicalDeviceImagelessFramebufferFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImagelessFramebufferFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImagelessFramebufferFeatures
p PhysicalDeviceImagelessFramebufferFeatures
x (Ptr PhysicalDeviceImagelessFramebufferFeatures -> IO b
f Ptr PhysicalDeviceImagelessFramebufferFeatures
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImagelessFramebufferFeatures
p PhysicalDeviceImagelessFramebufferFeatures{Bool
imagelessFramebuffer :: Bool
$sel:imagelessFramebuffer:PhysicalDeviceImagelessFramebufferFeatures :: PhysicalDeviceImagelessFramebufferFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGELESS_FRAMEBUFFER_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imagelessFramebuffer))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceImagelessFramebufferFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceImagelessFramebufferFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGELESS_FRAMEBUFFER_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceImagelessFramebufferFeatures where
peekCStruct :: Ptr PhysicalDeviceImagelessFramebufferFeatures
-> IO PhysicalDeviceImagelessFramebufferFeatures
peekCStruct Ptr PhysicalDeviceImagelessFramebufferFeatures
p = do
Bool32
imagelessFramebuffer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceImagelessFramebufferFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceImagelessFramebufferFeatures
PhysicalDeviceImagelessFramebufferFeatures
(Bool32 -> Bool
bool32ToBool Bool32
imagelessFramebuffer)
instance Storable PhysicalDeviceImagelessFramebufferFeatures where
sizeOf :: PhysicalDeviceImagelessFramebufferFeatures -> Int
sizeOf ~PhysicalDeviceImagelessFramebufferFeatures
_ = Int
24
alignment :: PhysicalDeviceImagelessFramebufferFeatures -> Int
alignment ~PhysicalDeviceImagelessFramebufferFeatures
_ = Int
8
peek :: Ptr PhysicalDeviceImagelessFramebufferFeatures
-> IO PhysicalDeviceImagelessFramebufferFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceImagelessFramebufferFeatures
-> PhysicalDeviceImagelessFramebufferFeatures -> IO ()
poke Ptr PhysicalDeviceImagelessFramebufferFeatures
ptr PhysicalDeviceImagelessFramebufferFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImagelessFramebufferFeatures
ptr PhysicalDeviceImagelessFramebufferFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceImagelessFramebufferFeatures where
zero :: PhysicalDeviceImagelessFramebufferFeatures
zero = Bool -> PhysicalDeviceImagelessFramebufferFeatures
PhysicalDeviceImagelessFramebufferFeatures
forall a. Zero a => a
zero
data FramebufferAttachmentsCreateInfo = FramebufferAttachmentsCreateInfo
{
FramebufferAttachmentsCreateInfo
-> Vector FramebufferAttachmentImageInfo
attachmentImageInfos :: Vector FramebufferAttachmentImageInfo }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FramebufferAttachmentsCreateInfo)
#endif
deriving instance Show FramebufferAttachmentsCreateInfo
instance ToCStruct FramebufferAttachmentsCreateInfo where
withCStruct :: forall b.
FramebufferAttachmentsCreateInfo
-> (Ptr FramebufferAttachmentsCreateInfo -> IO b) -> IO b
withCStruct FramebufferAttachmentsCreateInfo
x Ptr FramebufferAttachmentsCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr FramebufferAttachmentsCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr FramebufferAttachmentsCreateInfo
p FramebufferAttachmentsCreateInfo
x (Ptr FramebufferAttachmentsCreateInfo -> IO b
f Ptr FramebufferAttachmentsCreateInfo
p)
pokeCStruct :: forall b.
Ptr FramebufferAttachmentsCreateInfo
-> FramebufferAttachmentsCreateInfo -> IO b -> IO b
pokeCStruct Ptr FramebufferAttachmentsCreateInfo
p FramebufferAttachmentsCreateInfo{Vector FramebufferAttachmentImageInfo
attachmentImageInfos :: Vector FramebufferAttachmentImageInfo
$sel:attachmentImageInfos:FramebufferAttachmentsCreateInfo :: FramebufferAttachmentsCreateInfo
-> Vector FramebufferAttachmentImageInfo
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENTS_CREATE_INFO)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector FramebufferAttachmentImageInfo
attachmentImageInfos)) :: Word32))
Ptr FramebufferAttachmentImageInfo
pPAttachmentImageInfos' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @FramebufferAttachmentImageInfo ((forall a. Vector a -> Int
Data.Vector.length (Vector FramebufferAttachmentImageInfo
attachmentImageInfos)) forall a. Num a => a -> a -> a
* Int
48)
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i FramebufferAttachmentImageInfo
e -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr FramebufferAttachmentImageInfo
pPAttachmentImageInfos' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr FramebufferAttachmentImageInfo) (FramebufferAttachmentImageInfo
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) (Vector FramebufferAttachmentImageInfo
attachmentImageInfos)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr FramebufferAttachmentImageInfo))) (Ptr FramebufferAttachmentImageInfo
pPAttachmentImageInfos')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr FramebufferAttachmentsCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr FramebufferAttachmentsCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENTS_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct FramebufferAttachmentsCreateInfo where
peekCStruct :: Ptr FramebufferAttachmentsCreateInfo
-> IO FramebufferAttachmentsCreateInfo
peekCStruct Ptr FramebufferAttachmentsCreateInfo
p = do
Word32
attachmentImageInfoCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr FramebufferAttachmentImageInfo
pAttachmentImageInfos <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr FramebufferAttachmentImageInfo) ((Ptr FramebufferAttachmentsCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr FramebufferAttachmentImageInfo)))
Vector FramebufferAttachmentImageInfo
pAttachmentImageInfos' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
attachmentImageInfoCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @FramebufferAttachmentImageInfo ((Ptr FramebufferAttachmentImageInfo
pAttachmentImageInfos forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr FramebufferAttachmentImageInfo)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector FramebufferAttachmentImageInfo
-> FramebufferAttachmentsCreateInfo
FramebufferAttachmentsCreateInfo
Vector FramebufferAttachmentImageInfo
pAttachmentImageInfos'
instance Zero FramebufferAttachmentsCreateInfo where
zero :: FramebufferAttachmentsCreateInfo
zero = Vector FramebufferAttachmentImageInfo
-> FramebufferAttachmentsCreateInfo
FramebufferAttachmentsCreateInfo
forall a. Monoid a => a
mempty
data FramebufferAttachmentImageInfo = FramebufferAttachmentImageInfo
{
FramebufferAttachmentImageInfo -> ImageCreateFlags
flags :: ImageCreateFlags
,
FramebufferAttachmentImageInfo -> ImageUsageFlags
usage :: ImageUsageFlags
,
FramebufferAttachmentImageInfo -> Word32
width :: Word32
,
FramebufferAttachmentImageInfo -> Word32
height :: Word32
,
FramebufferAttachmentImageInfo -> Word32
layerCount :: Word32
,
FramebufferAttachmentImageInfo -> Vector Format
viewFormats :: Vector Format
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FramebufferAttachmentImageInfo)
#endif
deriving instance Show FramebufferAttachmentImageInfo
instance ToCStruct FramebufferAttachmentImageInfo where
withCStruct :: forall b.
FramebufferAttachmentImageInfo
-> (Ptr FramebufferAttachmentImageInfo -> IO b) -> IO b
withCStruct FramebufferAttachmentImageInfo
x Ptr FramebufferAttachmentImageInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr FramebufferAttachmentImageInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr FramebufferAttachmentImageInfo
p FramebufferAttachmentImageInfo
x (Ptr FramebufferAttachmentImageInfo -> IO b
f Ptr FramebufferAttachmentImageInfo
p)
pokeCStruct :: forall b.
Ptr FramebufferAttachmentImageInfo
-> FramebufferAttachmentImageInfo -> IO b -> IO b
pokeCStruct Ptr FramebufferAttachmentImageInfo
p FramebufferAttachmentImageInfo{Word32
Vector Format
ImageCreateFlags
ImageUsageFlags
viewFormats :: Vector Format
layerCount :: Word32
height :: Word32
width :: Word32
usage :: ImageUsageFlags
flags :: ImageCreateFlags
$sel:viewFormats:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> Vector Format
$sel:layerCount:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> Word32
$sel:height:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> Word32
$sel:width:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> Word32
$sel:usage:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> ImageUsageFlags
$sel:flags:FramebufferAttachmentImageInfo :: FramebufferAttachmentImageInfo -> ImageCreateFlags
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENT_IMAGE_INFO)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageCreateFlags)) (ImageCreateFlags
flags)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ImageUsageFlags)) (ImageUsageFlags
usage)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
width)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (Word32
height)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (Word32
layerCount)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Format
viewFormats)) :: Word32))
Ptr Format
pPViewFormats' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Format ((forall a. Vector a -> Int
Data.Vector.length (Vector Format
viewFormats)) forall a. Num a => a -> a -> a
* Int
4)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Format
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Format
pPViewFormats' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Format) (Format
e)) (Vector Format
viewFormats)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr Format))) (Ptr Format
pPViewFormats')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr FramebufferAttachmentImageInfo -> IO b -> IO b
pokeZeroCStruct Ptr FramebufferAttachmentImageInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENT_IMAGE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ImageUsageFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct FramebufferAttachmentImageInfo where
peekCStruct :: Ptr FramebufferAttachmentImageInfo
-> IO FramebufferAttachmentImageInfo
peekCStruct Ptr FramebufferAttachmentImageInfo
p = do
ImageCreateFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @ImageCreateFlags ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageCreateFlags))
ImageUsageFlags
usage <- forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ImageUsageFlags))
Word32
width <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
Word32
height <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
Word32
layerCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
Word32
viewFormatCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32))
Ptr Format
pViewFormats <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Format) ((Ptr FramebufferAttachmentImageInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr Format)))
Vector Format
pViewFormats' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
viewFormatCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr Format
pViewFormats forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Format)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ImageCreateFlags
-> ImageUsageFlags
-> Word32
-> Word32
-> Word32
-> Vector Format
-> FramebufferAttachmentImageInfo
FramebufferAttachmentImageInfo
ImageCreateFlags
flags ImageUsageFlags
usage Word32
width Word32
height Word32
layerCount Vector Format
pViewFormats'
instance Zero FramebufferAttachmentImageInfo where
zero :: FramebufferAttachmentImageInfo
zero = ImageCreateFlags
-> ImageUsageFlags
-> Word32
-> Word32
-> Word32
-> Vector Format
-> FramebufferAttachmentImageInfo
FramebufferAttachmentImageInfo
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Monoid a => a
mempty
data RenderPassAttachmentBeginInfo = RenderPassAttachmentBeginInfo
{
RenderPassAttachmentBeginInfo -> Vector ImageView
attachments :: Vector ImageView }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassAttachmentBeginInfo)
#endif
deriving instance Show RenderPassAttachmentBeginInfo
instance ToCStruct RenderPassAttachmentBeginInfo where
withCStruct :: forall b.
RenderPassAttachmentBeginInfo
-> (Ptr RenderPassAttachmentBeginInfo -> IO b) -> IO b
withCStruct RenderPassAttachmentBeginInfo
x Ptr RenderPassAttachmentBeginInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr RenderPassAttachmentBeginInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RenderPassAttachmentBeginInfo
p RenderPassAttachmentBeginInfo
x (Ptr RenderPassAttachmentBeginInfo -> IO b
f Ptr RenderPassAttachmentBeginInfo
p)
pokeCStruct :: forall b.
Ptr RenderPassAttachmentBeginInfo
-> RenderPassAttachmentBeginInfo -> IO b -> IO b
pokeCStruct Ptr RenderPassAttachmentBeginInfo
p RenderPassAttachmentBeginInfo{Vector ImageView
attachments :: Vector ImageView
$sel:attachments:RenderPassAttachmentBeginInfo :: RenderPassAttachmentBeginInfo -> Vector ImageView
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_ATTACHMENT_BEGIN_INFO)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector ImageView
attachments)) :: Word32))
Ptr ImageView
pPAttachments' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @ImageView ((forall a. Vector a -> Int
Data.Vector.length (Vector ImageView
attachments)) forall a. Num a => a -> a -> a
* Int
8)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ImageView
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ImageView
pPAttachments' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageView) (ImageView
e)) (Vector ImageView
attachments)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr ImageView))) (Ptr ImageView
pPAttachments')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr RenderPassAttachmentBeginInfo -> IO b -> IO b
pokeZeroCStruct Ptr RenderPassAttachmentBeginInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_ATTACHMENT_BEGIN_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct RenderPassAttachmentBeginInfo where
peekCStruct :: Ptr RenderPassAttachmentBeginInfo
-> IO RenderPassAttachmentBeginInfo
peekCStruct Ptr RenderPassAttachmentBeginInfo
p = do
Word32
attachmentCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr ImageView
pAttachments <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ImageView) ((Ptr RenderPassAttachmentBeginInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr ImageView)))
Vector ImageView
pAttachments' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
attachmentCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @ImageView ((Ptr ImageView
pAttachments forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageView)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector ImageView -> RenderPassAttachmentBeginInfo
RenderPassAttachmentBeginInfo
Vector ImageView
pAttachments'
instance Zero RenderPassAttachmentBeginInfo where
zero :: RenderPassAttachmentBeginInfo
zero = Vector ImageView -> RenderPassAttachmentBeginInfo
RenderPassAttachmentBeginInfo
forall a. Monoid a => a
mempty