{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_ycbcr_image_arrays  ( PhysicalDeviceYcbcrImageArraysFeaturesEXT(..)
                                                    , EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION
                                                    , pattern EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION
                                                    , EXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME
                                                    , pattern EXT_YCBCR_IMAGE_ARRAYS_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_YCBCR_IMAGE_ARRAYS_FEATURES_EXT))
-- | VkPhysicalDeviceYcbcrImageArraysFeaturesEXT - Structure describing
-- extended Y’CbCr image creation features that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceYcbcrImageArraysFeaturesEXT' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceYcbcrImageArraysFeaturesEXT' structure is included
-- in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceYcbcrImageArraysFeaturesEXT' /can/ also be included in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceYcbcrImageArraysFeaturesEXT = PhysicalDeviceYcbcrImageArraysFeaturesEXT
  { -- | @ycbcrImageArrays@ indicates that the implementation supports creating
    -- images with a format that requires
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion Y′CBCR conversion>
    -- and has multiple array layers.
    PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
ycbcrImageArrays :: Bool }
  deriving (Typeable, PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
(PhysicalDeviceYcbcrImageArraysFeaturesEXT
 -> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool)
-> (PhysicalDeviceYcbcrImageArraysFeaturesEXT
    -> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool)
-> Eq PhysicalDeviceYcbcrImageArraysFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
$c/= :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
== :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
$c== :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceYcbcrImageArraysFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceYcbcrImageArraysFeaturesEXT

instance ToCStruct PhysicalDeviceYcbcrImageArraysFeaturesEXT where
  withCStruct :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> (Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceYcbcrImageArraysFeaturesEXT
x f :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p -> Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p PhysicalDeviceYcbcrImageArraysFeaturesEXT
x (Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b
f Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p PhysicalDeviceYcbcrImageArraysFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_IMAGE_ARRAYS_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> 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 PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
ycbcrImageArrays))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_IMAGE_ARRAYS_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> 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 PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> 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 PhysicalDeviceYcbcrImageArraysFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> IO PhysicalDeviceYcbcrImageArraysFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p = do
    Bool32
ycbcrImageArrays <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT
p Ptr PhysicalDeviceYcbcrImageArraysFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> IO PhysicalDeviceYcbcrImageArraysFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceYcbcrImageArraysFeaturesEXT
 -> IO PhysicalDeviceYcbcrImageArraysFeaturesEXT)
-> PhysicalDeviceYcbcrImageArraysFeaturesEXT
-> IO PhysicalDeviceYcbcrImageArraysFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceYcbcrImageArraysFeaturesEXT
PhysicalDeviceYcbcrImageArraysFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
ycbcrImageArrays)

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

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


type EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION"
pattern EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION :: a
$mEXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_YCBCR_IMAGE_ARRAYS_SPEC_VERSION = 1


type EXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME = "VK_EXT_ycbcr_image_arrays"

-- No documentation found for TopLevel "VK_EXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME"
pattern EXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME :: a
$mEXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_YCBCR_IMAGE_ARRAYS_EXTENSION_NAME = "VK_EXT_ycbcr_image_arrays"