{-# language CPP #-}
-- | = Name
--
-- VK_NV_dedicated_allocation_image_aliasing - device extension
--
-- == VK_NV_dedicated_allocation_image_aliasing
--
-- [__Name String__]
--     @VK_NV_dedicated_allocation_image_aliasing@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     241
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_dedicated_allocation@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Nuno Subtil
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_dedicated_allocation_image_aliasing] @nsubtil%0A*Here describe the issue or question you have about the VK_NV_dedicated_allocation_image_aliasing extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-01-04
--
-- [__Contributors__]
--
--     -   Nuno Subtil, NVIDIA
--
--     -   Jeff Bolz, NVIDIA
--
--     -   Eric Werness, NVIDIA
--
--     -   Axel Gneiting, id Software
--
-- == Description
--
-- This extension allows applications to alias images on dedicated
-- allocations, subject to specific restrictions: the extent and the number
-- of layers in the image being aliased must be smaller than or equal to
-- those of the original image for which the allocation was created, and
-- every other image parameter must match.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV'
--
-- == New Enum Constants
--
-- -   'NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME'
--
-- -   'NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV'
--
-- == Version History
--
-- -   Revision 1, 2019-01-04 (Nuno Subtil)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_NV_dedicated_allocation_image_aliasing Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_NV_dedicated_allocation_image_aliasing  ( PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV(..)
                                                                    , NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION
                                                                    , pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION
                                                                    , NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME
                                                                    , pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_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_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV))
-- | VkPhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV - Structure
-- describing dedicated allocation image aliasing features that can be
-- supported by an implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV'
-- structure is included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV'
-- /can/ also be used in the @pNext@ chain of
-- 'Vulkan.Core10.Device.DeviceCreateInfo' to selectively enable these
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_dedicated_allocation_image_aliasing VK_NV_dedicated_allocation_image_aliasing>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV = PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
  { -- | #features-dedicatedAllocationImageAliasing#
    -- @dedicatedAllocationImageAliasing@ indicates that the implementation
    -- supports aliasing of compatible image objects on a dedicated allocation.
    PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
dedicatedAllocationImageAliasing :: Bool }
  deriving (Typeable, PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
(PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
 -> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
 -> Bool)
-> (PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
    -> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
    -> Bool)
-> Eq PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
$c/= :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
== :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
$c== :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV

instance ToCStruct PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV where
  withCStruct :: forall b.
PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
    -> IO b)
-> IO b
withCStruct PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
x Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
f = Int
-> (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
    -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
  -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p -> Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
x (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
f Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV{Bool
dedicatedAllocationImageAliasing :: Bool
$sel:dedicatedAllocationImageAliasing:PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocationImageAliasing))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

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

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

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


type NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION"
pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall a. Integral a => a
$mNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION = 1


type NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME = "VK_NV_dedicated_allocation_image_aliasing"

-- No documentation found for TopLevel "VK_NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME"
pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME = "VK_NV_dedicated_allocation_image_aliasing"