{-# language CPP #-}
-- | = Name
--
-- VK_EXT_4444_formats - device extension
--
-- == VK_EXT_4444_formats
--
-- [__Name String__]
--     @VK_EXT_4444_formats@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     341
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@ to be enabled
--         for any device-level functionality
--
-- [__Deprecation state__]
--
--     -   /Promoted/ to
--         <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.3-promotions Vulkan 1.3>
--
-- [__Contact__]
--
--     -   Joshua Ashton
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_4444_formats] @Joshua-Ashton%0A*Here describe the issue or question you have about the VK_EXT_4444_formats extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2020-07-28
--
-- [__Interactions and External Dependencies__]
--
--     -   Promoted to Vulkan 1.3 Core
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Joshua Ashton, Valve
--
--     -   Jason Ekstrand, Intel
--
-- == Description
--
-- This extension defines the 'FORMAT_A4R4G4B4_UNORM_PACK16_EXT' and
-- 'FORMAT_A4B4G4R4_UNORM_PACK16_EXT' formats which are defined in other
-- current graphics APIs.
--
-- This extension may be useful for building translation layers for those
-- APIs or for porting applications that use these formats without having
-- to resort to swizzles.
--
-- When VK_EXT_custom_border_color is used, these formats are not subject
-- to the same restrictions for border color without format as with
-- VK_FORMAT_B4G4R4A4_UNORM_PACK16.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDevice4444FormatsFeaturesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_4444_FORMATS_EXTENSION_NAME'
--
-- -   'EXT_4444_FORMATS_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.Format.Format':
--
--     -   'FORMAT_A4B4G4R4_UNORM_PACK16_EXT'
--
--     -   'FORMAT_A4R4G4B4_UNORM_PACK16_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT'
--
-- == Promotion to Vulkan 1.3
--
-- This extension has been partially promoted. The format enumerants
-- introduced by the extension are included in core Vulkan 1.3, with the
-- EXT suffix omitted. However, runtime support for these formats is
-- optional in core Vulkan 1.3, while if this extension is supported,
-- runtime support is mandatory. The feature structure is not promoted. The
-- original enum names are still available as aliases of the core
-- functionality.
--
-- == Version History
--
-- -   Revision 1, 2020-07-04 (Joshua Ashton)
--
--     -   Initial draft
--
-- == See Also
--
-- 'PhysicalDevice4444FormatsFeaturesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_4444_formats Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_4444_formats  ( pattern FORMAT_A4R4G4B4_UNORM_PACK16_EXT
                                              , pattern FORMAT_A4B4G4R4_UNORM_PACK16_EXT
                                              , PhysicalDevice4444FormatsFeaturesEXT(..)
                                              , EXT_4444_FORMATS_SPEC_VERSION
                                              , pattern EXT_4444_FORMATS_SPEC_VERSION
                                              , EXT_4444_FORMATS_EXTENSION_NAME
                                              , pattern EXT_4444_FORMATS_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.Format (Format(FORMAT_A4B4G4R4_UNORM_PACK16))
import Vulkan.Core10.Enums.Format (Format(FORMAT_A4R4G4B4_UNORM_PACK16))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT))
-- No documentation found for TopLevel "VK_FORMAT_A4R4G4B4_UNORM_PACK16_EXT"
pattern $bFORMAT_A4R4G4B4_UNORM_PACK16_EXT :: Format
$mFORMAT_A4R4G4B4_UNORM_PACK16_EXT :: forall {r}. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A4R4G4B4_UNORM_PACK16_EXT = FORMAT_A4R4G4B4_UNORM_PACK16


-- No documentation found for TopLevel "VK_FORMAT_A4B4G4R4_UNORM_PACK16_EXT"
pattern $bFORMAT_A4B4G4R4_UNORM_PACK16_EXT :: Format
$mFORMAT_A4B4G4R4_UNORM_PACK16_EXT :: forall {r}. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A4B4G4R4_UNORM_PACK16_EXT = FORMAT_A4B4G4R4_UNORM_PACK16


-- | VkPhysicalDevice4444FormatsFeaturesEXT - Structure describing additional
-- 4444 formats supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDevice4444FormatsFeaturesEXT' 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. 'PhysicalDevice4444FormatsFeaturesEXT' /can/ also be used in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- Note
--
-- Although the formats defined by the @VK_EXT_4444_formats@ extension were
-- promoted to Vulkan 1.3 as optional formats, the
-- 'PhysicalDevice4444FormatsFeaturesEXT' structure was not promoted to
-- Vulkan 1.3.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_4444_formats VK_EXT_4444_formats>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevice4444FormatsFeaturesEXT = PhysicalDevice4444FormatsFeaturesEXT
  { -- | #features-formatA4R4G4B4# @formatA4R4G4B4@ indicates that the
    -- implementation /must/ support using a
    -- 'Vulkan.Core10.Enums.Format.Format' of
    -- 'FORMAT_A4R4G4B4_UNORM_PACK16_EXT' with at least the following
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlagBits':
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT'
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
    PhysicalDevice4444FormatsFeaturesEXT -> Bool
formatA4R4G4B4 :: Bool
  , -- | #features-formatA4B4G4R4# @formatA4B4G4R4@ indicates that the
    -- implementation /must/ support using a
    -- 'Vulkan.Core10.Enums.Format.Format' of
    -- 'FORMAT_A4B4G4R4_UNORM_PACK16_EXT' with at least the following
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlagBits':
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT'
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_BLIT_SRC_BIT'
    --
    -- -   'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
    PhysicalDevice4444FormatsFeaturesEXT -> Bool
formatA4B4G4R4 :: Bool
  }
  deriving (Typeable, PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
(PhysicalDevice4444FormatsFeaturesEXT
 -> PhysicalDevice4444FormatsFeaturesEXT -> Bool)
-> (PhysicalDevice4444FormatsFeaturesEXT
    -> PhysicalDevice4444FormatsFeaturesEXT -> Bool)
-> Eq PhysicalDevice4444FormatsFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
$c/= :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
== :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
$c== :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevice4444FormatsFeaturesEXT)
#endif
deriving instance Show PhysicalDevice4444FormatsFeaturesEXT

instance ToCStruct PhysicalDevice4444FormatsFeaturesEXT where
  withCStruct :: forall b.
PhysicalDevice4444FormatsFeaturesEXT
-> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDevice4444FormatsFeaturesEXT
x Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b
f = Int -> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevice4444FormatsFeaturesEXT
p -> Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice4444FormatsFeaturesEXT
p PhysicalDevice4444FormatsFeaturesEXT
x (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b
f Ptr PhysicalDevice4444FormatsFeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice4444FormatsFeaturesEXT
p PhysicalDevice4444FormatsFeaturesEXT{Bool
formatA4B4G4R4 :: Bool
formatA4R4G4B4 :: Bool
$sel:formatA4B4G4R4:PhysicalDevice4444FormatsFeaturesEXT :: PhysicalDevice4444FormatsFeaturesEXT -> Bool
$sel:formatA4R4G4B4:PhysicalDevice4444FormatsFeaturesEXT :: PhysicalDevice4444FormatsFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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 PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
formatA4R4G4B4))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
formatA4B4G4R4))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevice4444FormatsFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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 PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

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

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

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


type EXT_4444_FORMATS_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_4444_FORMATS_SPEC_VERSION"
pattern EXT_4444_FORMATS_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_4444_FORMATS_SPEC_VERSION :: forall a. Integral a => a
$mEXT_4444_FORMATS_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_4444_FORMATS_SPEC_VERSION = 1


type EXT_4444_FORMATS_EXTENSION_NAME = "VK_EXT_4444_formats"

-- No documentation found for TopLevel "VK_EXT_4444_FORMATS_EXTENSION_NAME"
pattern EXT_4444_FORMATS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_4444_FORMATS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_4444_FORMATS_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_4444_FORMATS_EXTENSION_NAME = "VK_EXT_4444_formats"