{-# 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 (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX))
-- | VkPhysicalDeviceMultiviewPerViewAttributesPropertiesNVX - Structure
-- describing multiview limits that can be supported by an implementation
--
-- = Members
--
-- The members of the
-- 'PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX' structure
-- describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX' structure
-- is included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX = PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
  { -- | @perViewPositionAllComponents@ is 'Vulkan.Core10.FundamentalTypes.TRUE'
    -- if the implementation supports per-view position values that differ in
    -- components other than the X component.
    PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
perViewPositionAllComponents :: Bool }
  deriving (Typeable, PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool
(PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
 -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool)
-> (PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
    -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Bool)
-> Eq PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
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 :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> (Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
    -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
x f :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
  -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p -> Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b
-> IO b
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 :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b
-> IO b
pokeCStruct p :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
perViewPositionAllComponents))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
  peekCStruct :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
peekCStruct p :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p = do
    Bool32
perViewPositionAllComponents <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
p Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
 -> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX)
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
             (Bool32 -> Bool
bool32ToBool Bool32
perViewPositionAllComponents)

instance Storable PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
  sizeOf :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Int
sizeOf ~PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
_ = 24
  alignment :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> Int
alignment ~PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
_ = 8
  peek :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
peek = Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX -> IO ()
poke ptr :: Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
ptr poked :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
poked = Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
ptr PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX where
  zero :: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
zero = Bool -> PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX
           Bool
forall a. Zero a => a
zero


type NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION"
pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: forall a . Integral a => a
pattern $bNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: a
$mNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_SPEC_VERSION = 1


type NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME = "VK_NVX_multiview_per_view_attributes"

-- No documentation found for TopLevel "VK_NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME"
pattern NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: a
$mNVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NVX_MULTIVIEW_PER_VIEW_ATTRIBUTES_EXTENSION_NAME = "VK_NVX_multiview_per_view_attributes"