{-# language CPP #-}
module Vulkan.Extensions.VK_NVX_multiview_per_view_attributes ( PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX(..)
, NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION
, pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION
, NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME
, pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_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_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX))
data PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX = PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
{
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
perViewPositionAllComponents :: Bool }
deriving (Typeable, PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
$c/= :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
== :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
$c== :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX)
#endif
deriving instance Show PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
instance ToCStruct PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
withCStruct :: forall b.
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> (Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b)
-> IO b
withCStruct PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
x Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
x (Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> IO b
f Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX{Bool
perViewPositionAllComponents :: Bool
$sel:perViewPositionAllComponents:PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
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 PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
perViewPositionAllComponents))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
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 PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
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 PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
peekCStruct :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
peekCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p = do
Bool32
perViewPositionAllComponents <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
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 -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
(Bool32 -> Bool
bool32ToBool Bool32
perViewPositionAllComponents)
instance Storable PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
sizeOf :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Int
sizeOf ~PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
_ = Int
24
alignment :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Int
alignment ~PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
_ = Int
8
peek :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> IO ()
poke Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
zero :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
zero = Bool -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
forall a. Zero a => a
zero
type NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION = 1
pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: forall a . Integral a => a
pattern $bNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: forall a. Integral a => a
$mNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION = 1
type NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME = "VK_NVX_multiview_per_view_attributes"
pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME = "VK_NVX_multiview_per_view_attributes"