{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_attachment_feedback_loop_layout ( PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT(..)
, EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION
, pattern EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION
, EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME
, pattern EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_FEATURES_EXT))
data PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT = PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
{
PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
attachmentFeedbackLoopLayout :: Bool }
deriving (Typeable, PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
$c/= :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
== :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
$c== :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
instance ToCStruct PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> (Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> IO b)
-> IO b
withCStruct PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
x Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
x (Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> IO b
f Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT{Bool
attachmentFeedbackLoopLayout :: Bool
$sel:attachmentFeedbackLoopLayout:PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
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 PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
attachmentFeedbackLoopLayout))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
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 PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
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 PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> IO PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
peekCStruct Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
p = do
Bool32
attachmentFeedbackLoopLayout <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
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 -> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
attachmentFeedbackLoopLayout)
instance Storable PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT where
sizeOf :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Int
sizeOf ~PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> Int
alignment ~PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> IO PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
-> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
ptr PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT where
zero :: PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
zero = Bool -> PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
PhysicalDeviceAttachmentFeedbackLoopLayoutFeaturesEXT
forall a. Zero a => a
zero
type EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION = 2
pattern EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION :: forall a. Integral a => a
$mEXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_SPEC_VERSION = 2
type EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME = "VK_EXT_attachment_feedback_loop_layout"
pattern EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ATTACHMENT_FEEDBACK_LOOP_LAYOUT_EXTENSION_NAME = "VK_EXT_attachment_feedback_loop_layout"