{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 ( InputAttachmentAspectReference(..)
, RenderPassInputAttachmentAspectCreateInfo(..)
, PhysicalDevicePointClippingProperties(..)
, ImageViewUsageCreateInfo(..)
, PipelineTessellationDomainOriginStateCreateInfo(..)
, ImageLayout(..)
, StructureType(..)
, ImageCreateFlagBits(..)
, ImageCreateFlags
, PointClippingBehavior(..)
, TessellationDomainOrigin(..)
) 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.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core11.Enums.PointClippingBehavior (PointClippingBehavior)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlagBits(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..))
import Vulkan.Core11.Enums.PointClippingBehavior (PointClippingBehavior(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin(..))
data InputAttachmentAspectReference = InputAttachmentAspectReference
{
InputAttachmentAspectReference -> Word32
subpass :: Word32
,
InputAttachmentAspectReference -> Word32
inputAttachmentIndex :: Word32
,
InputAttachmentAspectReference -> ImageAspectFlags
aspectMask :: ImageAspectFlags
}
deriving (Typeable, InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
$c/= :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
== :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
$c== :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (InputAttachmentAspectReference)
#endif
deriving instance Show InputAttachmentAspectReference
instance ToCStruct InputAttachmentAspectReference where
withCStruct :: forall b.
InputAttachmentAspectReference
-> (Ptr InputAttachmentAspectReference -> IO b) -> IO b
withCStruct InputAttachmentAspectReference
x Ptr InputAttachmentAspectReference -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
12 forall a b. (a -> b) -> a -> b
$ \Ptr InputAttachmentAspectReference
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr InputAttachmentAspectReference
p InputAttachmentAspectReference
x (Ptr InputAttachmentAspectReference -> IO b
f Ptr InputAttachmentAspectReference
p)
pokeCStruct :: forall b.
Ptr InputAttachmentAspectReference
-> InputAttachmentAspectReference -> IO b -> IO b
pokeCStruct Ptr InputAttachmentAspectReference
p InputAttachmentAspectReference{Word32
ImageAspectFlags
aspectMask :: ImageAspectFlags
inputAttachmentIndex :: Word32
subpass :: Word32
$sel:aspectMask:InputAttachmentAspectReference :: InputAttachmentAspectReference -> ImageAspectFlags
$sel:inputAttachmentIndex:InputAttachmentAspectReference :: InputAttachmentAspectReference -> Word32
$sel:subpass:InputAttachmentAspectReference :: InputAttachmentAspectReference -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
subpass)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
inputAttachmentIndex)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
IO b
f
cStructSize :: Int
cStructSize = Int
12
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: forall b. Ptr InputAttachmentAspectReference -> IO b -> IO b
pokeZeroCStruct Ptr InputAttachmentAspectReference
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct InputAttachmentAspectReference where
peekCStruct :: Ptr InputAttachmentAspectReference
-> IO InputAttachmentAspectReference
peekCStruct Ptr InputAttachmentAspectReference
p = do
Word32
subpass <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
Word32
inputAttachmentIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
ImageAspectFlags
aspectMask <- forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr InputAttachmentAspectReference
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Word32 -> ImageAspectFlags -> InputAttachmentAspectReference
InputAttachmentAspectReference
Word32
subpass Word32
inputAttachmentIndex ImageAspectFlags
aspectMask
instance Storable InputAttachmentAspectReference where
sizeOf :: InputAttachmentAspectReference -> Int
sizeOf ~InputAttachmentAspectReference
_ = Int
12
alignment :: InputAttachmentAspectReference -> Int
alignment ~InputAttachmentAspectReference
_ = Int
4
peek :: Ptr InputAttachmentAspectReference
-> IO InputAttachmentAspectReference
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr InputAttachmentAspectReference
-> InputAttachmentAspectReference -> IO ()
poke Ptr InputAttachmentAspectReference
ptr InputAttachmentAspectReference
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr InputAttachmentAspectReference
ptr InputAttachmentAspectReference
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero InputAttachmentAspectReference where
zero :: InputAttachmentAspectReference
zero = Word32
-> Word32 -> ImageAspectFlags -> InputAttachmentAspectReference
InputAttachmentAspectReference
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data RenderPassInputAttachmentAspectCreateInfo = RenderPassInputAttachmentAspectCreateInfo
{
RenderPassInputAttachmentAspectCreateInfo
-> Vector InputAttachmentAspectReference
aspectReferences :: Vector InputAttachmentAspectReference }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassInputAttachmentAspectCreateInfo)
#endif
deriving instance Show RenderPassInputAttachmentAspectCreateInfo
instance ToCStruct RenderPassInputAttachmentAspectCreateInfo where
withCStruct :: forall b.
RenderPassInputAttachmentAspectCreateInfo
-> (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b) -> IO b
withCStruct RenderPassInputAttachmentAspectCreateInfo
x Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr RenderPassInputAttachmentAspectCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p RenderPassInputAttachmentAspectCreateInfo
x (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b
f Ptr RenderPassInputAttachmentAspectCreateInfo
p)
pokeCStruct :: forall b.
Ptr RenderPassInputAttachmentAspectCreateInfo
-> RenderPassInputAttachmentAspectCreateInfo -> IO b -> IO b
pokeCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p RenderPassInputAttachmentAspectCreateInfo{Vector InputAttachmentAspectReference
aspectReferences :: Vector InputAttachmentAspectReference
$sel:aspectReferences:RenderPassInputAttachmentAspectCreateInfo :: RenderPassInputAttachmentAspectCreateInfo
-> Vector InputAttachmentAspectReference
..} 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 RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_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 RenderPassInputAttachmentAspectCreateInfo
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 RenderPassInputAttachmentAspectCreateInfo
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 InputAttachmentAspectReference
aspectReferences)) :: Word32))
Ptr InputAttachmentAspectReference
pPAspectReferences' <- 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 @InputAttachmentAspectReference ((forall a. Vector a -> Int
Data.Vector.length (Vector InputAttachmentAspectReference
aspectReferences)) forall a. Num a => a -> a -> a
* Int
12)
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 InputAttachmentAspectReference
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr InputAttachmentAspectReference
pPAspectReferences' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
12 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr InputAttachmentAspectReference) (InputAttachmentAspectReference
e)) (Vector InputAttachmentAspectReference
aspectReferences)
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 RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr InputAttachmentAspectReference))) (Ptr InputAttachmentAspectReference
pPAspectReferences')
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 RenderPassInputAttachmentAspectCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct RenderPassInputAttachmentAspectCreateInfo where
peekCStruct :: Ptr RenderPassInputAttachmentAspectCreateInfo
-> IO RenderPassInputAttachmentAspectCreateInfo
peekCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p = do
Word32
aspectReferenceCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr InputAttachmentAspectReference
pAspectReferences <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr InputAttachmentAspectReference) ((Ptr RenderPassInputAttachmentAspectCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr InputAttachmentAspectReference)))
Vector InputAttachmentAspectReference
pAspectReferences' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
aspectReferenceCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @InputAttachmentAspectReference ((Ptr InputAttachmentAspectReference
pAspectReferences forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
12 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr InputAttachmentAspectReference)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector InputAttachmentAspectReference
-> RenderPassInputAttachmentAspectCreateInfo
RenderPassInputAttachmentAspectCreateInfo
Vector InputAttachmentAspectReference
pAspectReferences'
instance Zero RenderPassInputAttachmentAspectCreateInfo where
zero :: RenderPassInputAttachmentAspectCreateInfo
zero = Vector InputAttachmentAspectReference
-> RenderPassInputAttachmentAspectCreateInfo
RenderPassInputAttachmentAspectCreateInfo
forall a. Monoid a => a
mempty
data PhysicalDevicePointClippingProperties = PhysicalDevicePointClippingProperties
{
PhysicalDevicePointClippingProperties -> PointClippingBehavior
pointClippingBehavior :: PointClippingBehavior }
deriving (Typeable, PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
$c/= :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
== :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
$c== :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePointClippingProperties)
#endif
deriving instance Show PhysicalDevicePointClippingProperties
instance ToCStruct PhysicalDevicePointClippingProperties where
withCStruct :: forall b.
PhysicalDevicePointClippingProperties
-> (Ptr PhysicalDevicePointClippingProperties -> IO b) -> IO b
withCStruct PhysicalDevicePointClippingProperties
x Ptr PhysicalDevicePointClippingProperties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePointClippingProperties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePointClippingProperties
p PhysicalDevicePointClippingProperties
x (Ptr PhysicalDevicePointClippingProperties -> IO b
f Ptr PhysicalDevicePointClippingProperties
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePointClippingProperties
p PhysicalDevicePointClippingProperties{PointClippingBehavior
pointClippingBehavior :: PointClippingBehavior
$sel:pointClippingBehavior:PhysicalDevicePointClippingProperties :: PhysicalDevicePointClippingProperties -> PointClippingBehavior
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePointClippingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePointClippingProperties
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 PhysicalDevicePointClippingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PointClippingBehavior)) (PointClippingBehavior
pointClippingBehavior)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDevicePointClippingProperties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePointClippingProperties
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePointClippingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePointClippingProperties
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 PhysicalDevicePointClippingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PointClippingBehavior)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDevicePointClippingProperties where
peekCStruct :: Ptr PhysicalDevicePointClippingProperties
-> IO PhysicalDevicePointClippingProperties
peekCStruct Ptr PhysicalDevicePointClippingProperties
p = do
PointClippingBehavior
pointClippingBehavior <- forall a. Storable a => Ptr a -> IO a
peek @PointClippingBehavior ((Ptr PhysicalDevicePointClippingProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PointClippingBehavior))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PointClippingBehavior -> PhysicalDevicePointClippingProperties
PhysicalDevicePointClippingProperties
PointClippingBehavior
pointClippingBehavior
instance Storable PhysicalDevicePointClippingProperties where
sizeOf :: PhysicalDevicePointClippingProperties -> Int
sizeOf ~PhysicalDevicePointClippingProperties
_ = Int
24
alignment :: PhysicalDevicePointClippingProperties -> Int
alignment ~PhysicalDevicePointClippingProperties
_ = Int
8
peek :: Ptr PhysicalDevicePointClippingProperties
-> IO PhysicalDevicePointClippingProperties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> IO ()
poke Ptr PhysicalDevicePointClippingProperties
ptr PhysicalDevicePointClippingProperties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePointClippingProperties
ptr PhysicalDevicePointClippingProperties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePointClippingProperties where
zero :: PhysicalDevicePointClippingProperties
zero = PointClippingBehavior -> PhysicalDevicePointClippingProperties
PhysicalDevicePointClippingProperties
forall a. Zero a => a
zero
data ImageViewUsageCreateInfo = ImageViewUsageCreateInfo
{
ImageViewUsageCreateInfo -> ImageUsageFlags
usage :: ImageUsageFlags }
deriving (Typeable, ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
$c/= :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
== :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
$c== :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewUsageCreateInfo)
#endif
deriving instance Show ImageViewUsageCreateInfo
instance ToCStruct ImageViewUsageCreateInfo where
withCStruct :: forall b.
ImageViewUsageCreateInfo
-> (Ptr ImageViewUsageCreateInfo -> IO b) -> IO b
withCStruct ImageViewUsageCreateInfo
x Ptr ImageViewUsageCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ImageViewUsageCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewUsageCreateInfo
p ImageViewUsageCreateInfo
x (Ptr ImageViewUsageCreateInfo -> IO b
f Ptr ImageViewUsageCreateInfo
p)
pokeCStruct :: forall b.
Ptr ImageViewUsageCreateInfo
-> ImageViewUsageCreateInfo -> IO b -> IO b
pokeCStruct Ptr ImageViewUsageCreateInfo
p ImageViewUsageCreateInfo{ImageUsageFlags
usage :: ImageUsageFlags
$sel:usage:ImageViewUsageCreateInfo :: ImageViewUsageCreateInfo -> ImageUsageFlags
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewUsageCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewUsageCreateInfo
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 ImageViewUsageCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageUsageFlags)) (ImageUsageFlags
usage)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ImageViewUsageCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr ImageViewUsageCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewUsageCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewUsageCreateInfo
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 ImageViewUsageCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageUsageFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewUsageCreateInfo where
peekCStruct :: Ptr ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo
peekCStruct Ptr ImageViewUsageCreateInfo
p = do
ImageUsageFlags
usage <- forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr ImageViewUsageCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageUsageFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ImageUsageFlags -> ImageViewUsageCreateInfo
ImageViewUsageCreateInfo
ImageUsageFlags
usage
instance Storable ImageViewUsageCreateInfo where
sizeOf :: ImageViewUsageCreateInfo -> Int
sizeOf ~ImageViewUsageCreateInfo
_ = Int
24
alignment :: ImageViewUsageCreateInfo -> Int
alignment ~ImageViewUsageCreateInfo
_ = Int
8
peek :: Ptr ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> IO ()
poke Ptr ImageViewUsageCreateInfo
ptr ImageViewUsageCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewUsageCreateInfo
ptr ImageViewUsageCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewUsageCreateInfo where
zero :: ImageViewUsageCreateInfo
zero = ImageUsageFlags -> ImageViewUsageCreateInfo
ImageViewUsageCreateInfo
forall a. Zero a => a
zero
data PipelineTessellationDomainOriginStateCreateInfo = PipelineTessellationDomainOriginStateCreateInfo
{
PipelineTessellationDomainOriginStateCreateInfo
-> TessellationDomainOrigin
domainOrigin :: TessellationDomainOrigin }
deriving (Typeable, PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
$c/= :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
== :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
$c== :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineTessellationDomainOriginStateCreateInfo)
#endif
deriving instance Show PipelineTessellationDomainOriginStateCreateInfo
instance ToCStruct PipelineTessellationDomainOriginStateCreateInfo where
withCStruct :: forall b.
PipelineTessellationDomainOriginStateCreateInfo
-> (Ptr PipelineTessellationDomainOriginStateCreateInfo -> IO b)
-> IO b
withCStruct PipelineTessellationDomainOriginStateCreateInfo
x Ptr PipelineTessellationDomainOriginStateCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PipelineTessellationDomainOriginStateCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
p PipelineTessellationDomainOriginStateCreateInfo
x (Ptr PipelineTessellationDomainOriginStateCreateInfo -> IO b
f Ptr PipelineTessellationDomainOriginStateCreateInfo
p)
pokeCStruct :: forall b.
Ptr PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> IO b -> IO b
pokeCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
p PipelineTessellationDomainOriginStateCreateInfo{TessellationDomainOrigin
domainOrigin :: TessellationDomainOrigin
$sel:domainOrigin:PipelineTessellationDomainOriginStateCreateInfo :: PipelineTessellationDomainOriginStateCreateInfo
-> TessellationDomainOrigin
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineTessellationDomainOriginStateCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineTessellationDomainOriginStateCreateInfo
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 PipelineTessellationDomainOriginStateCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TessellationDomainOrigin)) (TessellationDomainOrigin
domainOrigin)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PipelineTessellationDomainOriginStateCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineTessellationDomainOriginStateCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineTessellationDomainOriginStateCreateInfo
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 PipelineTessellationDomainOriginStateCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TessellationDomainOrigin)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineTessellationDomainOriginStateCreateInfo where
peekCStruct :: Ptr PipelineTessellationDomainOriginStateCreateInfo
-> IO PipelineTessellationDomainOriginStateCreateInfo
peekCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
p = do
TessellationDomainOrigin
domainOrigin <- forall a. Storable a => Ptr a -> IO a
peek @TessellationDomainOrigin ((Ptr PipelineTessellationDomainOriginStateCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TessellationDomainOrigin))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ TessellationDomainOrigin
-> PipelineTessellationDomainOriginStateCreateInfo
PipelineTessellationDomainOriginStateCreateInfo
TessellationDomainOrigin
domainOrigin
instance Storable PipelineTessellationDomainOriginStateCreateInfo where
sizeOf :: PipelineTessellationDomainOriginStateCreateInfo -> Int
sizeOf ~PipelineTessellationDomainOriginStateCreateInfo
_ = Int
24
alignment :: PipelineTessellationDomainOriginStateCreateInfo -> Int
alignment ~PipelineTessellationDomainOriginStateCreateInfo
_ = Int
8
peek :: Ptr PipelineTessellationDomainOriginStateCreateInfo
-> IO PipelineTessellationDomainOriginStateCreateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> IO ()
poke Ptr PipelineTessellationDomainOriginStateCreateInfo
ptr PipelineTessellationDomainOriginStateCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
ptr PipelineTessellationDomainOriginStateCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineTessellationDomainOriginStateCreateInfo where
zero :: PipelineTessellationDomainOriginStateCreateInfo
zero = TessellationDomainOrigin
-> PipelineTessellationDomainOriginStateCreateInfo
PipelineTessellationDomainOriginStateCreateInfo
forall a. Zero a => a
zero