{-# language CPP #-}
module Vulkan.Extensions.VK_NV_corner_sampled_image  ( PhysicalDeviceCornerSampledImageFeaturesNV(..)
                                                     , NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION
                                                     , pattern NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION
                                                     , NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME
                                                     , pattern NV_CORNER_SAMPLED_IMAGE_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_CORNER_SAMPLED_IMAGE_FEATURES_NV))
-- | VkPhysicalDeviceCornerSampledImageFeaturesNV - Structure describing
-- corner sampled image features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceCornerSampledImageFeaturesNV'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceCornerSampledImageFeaturesNV' 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 each feature is supported.
-- 'PhysicalDeviceCornerSampledImageFeaturesNV' /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 PhysicalDeviceCornerSampledImageFeaturesNV = PhysicalDeviceCornerSampledImageFeaturesNV
  { -- | @cornerSampledImage@ specifies whether images can be created with a
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV'.
    -- See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-images-corner-sampled Corner-Sampled Images>.
    PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
cornerSampledImage :: Bool }
  deriving (Typeable, PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
(PhysicalDeviceCornerSampledImageFeaturesNV
 -> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool)
-> (PhysicalDeviceCornerSampledImageFeaturesNV
    -> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool)
-> Eq PhysicalDeviceCornerSampledImageFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
$c/= :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
== :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
$c== :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCornerSampledImageFeaturesNV)
#endif
deriving instance Show PhysicalDeviceCornerSampledImageFeaturesNV

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

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

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


type NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION"
pattern NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: a
$mNV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION = 2


type NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME = "VK_NV_corner_sampled_image"

-- No documentation found for TopLevel "VK_NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME"
pattern NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: a
$mNV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME = "VK_NV_corner_sampled_image"