{-# language CPP #-}
module Vulkan.Core10.Enums.FormatFeatureFlagBits  ( FormatFeatureFlagBits( FORMAT_FEATURE_SAMPLED_IMAGE_BIT
                                                                         , FORMAT_FEATURE_STORAGE_IMAGE_BIT
                                                                         , FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT
                                                                         , FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT
                                                                         , FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT
                                                                         , FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT
                                                                         , FORMAT_FEATURE_VERTEX_BUFFER_BIT
                                                                         , FORMAT_FEATURE_COLOR_ATTACHMENT_BIT
                                                                         , FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT
                                                                         , FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT
                                                                         , FORMAT_FEATURE_BLIT_SRC_BIT
                                                                         , FORMAT_FEATURE_BLIT_DST_BIT
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT
                                                                         , FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR
                                                                         , FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT
                                                                         , FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT
                                                                         , FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT
                                                                         , FORMAT_FEATURE_DISJOINT_BIT
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT
                                                                         , FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT
                                                                         , FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT
                                                                         , FORMAT_FEATURE_TRANSFER_DST_BIT
                                                                         , FORMAT_FEATURE_TRANSFER_SRC_BIT
                                                                         , ..
                                                                         )
                                                  , FormatFeatureFlags
                                                  ) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
-- | VkFormatFeatureFlagBits - Bitmask specifying features supported by a
-- buffer
--
-- = Description
--
-- The following bits /may/ be set in @linearTilingFeatures@,
-- @optimalTilingFeatures@, and
-- 'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.DrmFormatModifierPropertiesEXT'::@drmFormatModifierTilingFeatures@,
-- specifying that the features are supported by <VkImage.html images> or
-- <VkImageView.html image views> or
-- <VkSamplerYcbcrConversion.html sampler Y′CBCR conversion objects>
-- created with the queried
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties'::@format@:
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' specifies that an image view
--     /can/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampledimage sampled from>.
--
-- -   'FORMAT_FEATURE_STORAGE_IMAGE_BIT' specifies that an image view
--     /can/ be used as a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storageimage storage images>.
--
-- -   'FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' specifies that an image
--     view /can/ be used as storage image that supports atomic operations.
--
-- -   'FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' specifies that an image view
--     /can/ be used as a framebuffer color attachment and as an input
--     attachment.
--
-- -   'FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT' specifies that an image
--     view /can/ be used as a framebuffer color attachment that supports
--     blending and as an input attachment.
--
-- -   'FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' specifies that an
--     image view /can/ be used as a framebuffer depth\/stencil attachment
--     and as an input attachment.
--
-- -   'FORMAT_FEATURE_BLIT_SRC_BIT' specifies that an image /can/ be used
--     as @srcImage@ for the
--     'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR' and
--     'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' commands.
--
-- -   'FORMAT_FEATURE_BLIT_DST_BIT' specifies that an image /can/ be used
--     as @dstImage@ for the
--     'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR' and
--     'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' commands.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' specifies that if
--     'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' is also set, an image view /can/
--     be used with a sampler that has either of @magFilter@ or @minFilter@
--     set to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR', or @mipmapMode@
--     set to
--     'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_LINEAR'.
--     If 'FORMAT_FEATURE_BLIT_SRC_BIT' is also set, an image can be used
--     as the @srcImage@ to
--     'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR' and
--     'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' with a @filter@
--     of 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR'. This bit /must/ only
--     be exposed for formats that also support the
--     'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' or 'FORMAT_FEATURE_BLIT_SRC_BIT'.
--
--     If the format being queried is a depth\/stencil format, this bit
--     only specifies that the depth aspect (not the stencil aspect) of an
--     image of this format supports linear filtering, and that linear
--     filtering of the depth aspect is supported whether depth compare is
--     enabled in the sampler or not. If this bit is not present, linear
--     filtering with depth compare disabled is unsupported and linear
--     filtering with depth compare enabled is supported, but /may/ compute
--     the filtered value in an implementation-dependent manner which
--     differs from the normal rules of linear filtering. The resulting
--     value /must/ be in the range [0,1] and /should/ be proportional to,
--     or a weighted average of, the number of comparison passes or
--     failures.
--
-- -   'FORMAT_FEATURE_TRANSFER_SRC_BIT' specifies that an image /can/ be
--     used as a source image for
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies copy commands>.
--
-- -   'FORMAT_FEATURE_TRANSFER_DST_BIT' specifies that an image /can/ be
--     used as a destination image for
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies copy commands>
--     and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears clear commands>.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT' specifies
--     'Vulkan.Core10.Handles.Image' /can/ be used as a sampled image with
--     a min or max
--     'Vulkan.Core12.Enums.SamplerReductionMode.SamplerReductionMode'.
--     This bit /must/ only be exposed for formats that also support the
--     'FORMAT_FEATURE_SAMPLED_IMAGE_BIT'.
--
-- -   'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT'
--     specifies that 'Vulkan.Core10.Handles.Image' /can/ be used with a
--     sampler that has either of @magFilter@ or @minFilter@ set to
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT', or be the
--     source image for a blit with @filter@ set to
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT'. This bit
--     /must/ only be exposed for formats that also support the
--     'FORMAT_FEATURE_SAMPLED_IMAGE_BIT'. If the format being queried is a
--     depth\/stencil format, this only specifies that the depth aspect is
--     cubic filterable.
--
-- -   'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT' specifies that an
--     application /can/ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
--     using this format as a source, and that an image of this format
--     /can/ be used with a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'
--     @xChromaOffset@ and\/or @yChromaOffset@ of
--     'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_MIDPOINT'.
--     Otherwise both @xChromaOffset@ and @yChromaOffset@ /must/ be
--     'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_COSITED_EVEN'.
--     If a format does not incorporate chroma downsampling (it is not a
--     “422” or “420” format) but the implementation supports sampler
--     Y′CBCR conversion for this format, the implementation /must/ set
--     'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT'.
--
-- -   'FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT' specifies that an
--     application /can/ define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
--     using this format as a source, and that an image of this format
--     /can/ be used with a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'
--     @xChromaOffset@ and\/or @yChromaOffset@ of
--     'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_COSITED_EVEN'.
--     Otherwise both @xChromaOffset@ and @yChromaOffset@ /must/ be
--     'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_MIDPOINT'. If
--     neither 'FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT' nor
--     'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT' is set, the application
--     /must/ not define a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
--     using this format as a source.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT'
--     specifies that the format can do linear sampler filtering
--     (min\/magFilter) whilst sampler Y′CBCR conversion is enabled.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT'
--     specifies that the format can have different chroma, min, and mag
--     filters.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT'
--     specifies that reconstruction is explicit, as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-chroma-reconstruction>.
--     If this bit is not present, reconstruction is implicit by default.
--
-- -   'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT'
--     specifies that reconstruction /can/ be forcibly made explicit by
--     setting
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'::@forceExplicitReconstruction@
--     to 'Vulkan.Core10.FundamentalTypes.TRUE'. If the format being
--     queried supports
--     'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT'
--     it /must/ also support
--     'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT'.
--
-- -   'FORMAT_FEATURE_DISJOINT_BIT' specifies that a multi-planar image
--     /can/ have the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_DISJOINT_BIT'
--     set during image creation. An implementation /must/ not set
--     'FORMAT_FEATURE_DISJOINT_BIT' for /single-plane formats/.
--
-- -   'FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT' specifies that an
--     image view /can/ be used as a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-fragmentdensitymapattachment fragment density map attachment>.
--
-- -   'FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' specifies
--     that an image view /can/ be used as a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment>.
--     An implementation /must/ not set this feature for formats that with
--     numeric type other than @*UINT@, or set it as a buffer feature.
--
-- The following bits /may/ be set in @bufferFeatures@, specifying that the
-- features are supported by <VkBuffer.html buffers> or
-- <VkBufferView.html buffer views> created with the queried
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceProperties'::@format@:
--
-- -   'FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT' specifies that the format
--     /can/ be used to create a buffer view that /can/ be bound to a
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
--     descriptor.
--
-- -   'FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT' specifies that the format
--     /can/ be used to create a buffer view that /can/ be bound to a
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
--     descriptor.
--
-- -   'FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' specifies that
--     atomic operations are supported on
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
--     with this format.
--
-- -   'FORMAT_FEATURE_VERTEX_BUFFER_BIT' specifies that the format /can/
--     be used as a vertex attribute format
--     ('Vulkan.Core10.Pipeline.VertexInputAttributeDescription'::@format@).
--
-- = See Also
--
-- 'FormatFeatureFlags'
newtype FormatFeatureFlagBits = FormatFeatureFlagBits Flags
  deriving newtype (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
(FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> Eq FormatFeatureFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c/= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
== :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c== :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
Eq, Eq FormatFeatureFlagBits
Eq FormatFeatureFlagBits =>
(FormatFeatureFlagBits -> FormatFeatureFlagBits -> Ordering)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits
    -> FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits
    -> FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> Ord FormatFeatureFlagBits
FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
FormatFeatureFlagBits -> FormatFeatureFlagBits -> Ordering
FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$cmin :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
max :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$cmax :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
>= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c>= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
> :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c> :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
<= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c<= :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
< :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
$c< :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Bool
compare :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Ordering
$ccompare :: FormatFeatureFlagBits -> FormatFeatureFlagBits -> Ordering
$cp1Ord :: Eq FormatFeatureFlagBits
Ord, Ptr b -> Int -> IO FormatFeatureFlagBits
Ptr b -> Int -> FormatFeatureFlagBits -> IO ()
Ptr FormatFeatureFlagBits -> IO FormatFeatureFlagBits
Ptr FormatFeatureFlagBits -> Int -> IO FormatFeatureFlagBits
Ptr FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits -> IO ()
Ptr FormatFeatureFlagBits -> FormatFeatureFlagBits -> IO ()
FormatFeatureFlagBits -> Int
(FormatFeatureFlagBits -> Int)
-> (FormatFeatureFlagBits -> Int)
-> (Ptr FormatFeatureFlagBits -> Int -> IO FormatFeatureFlagBits)
-> (Ptr FormatFeatureFlagBits
    -> Int -> FormatFeatureFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO FormatFeatureFlagBits)
-> (forall b. Ptr b -> Int -> FormatFeatureFlagBits -> IO ())
-> (Ptr FormatFeatureFlagBits -> IO FormatFeatureFlagBits)
-> (Ptr FormatFeatureFlagBits -> FormatFeatureFlagBits -> IO ())
-> Storable FormatFeatureFlagBits
forall b. Ptr b -> Int -> IO FormatFeatureFlagBits
forall b. Ptr b -> Int -> FormatFeatureFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr FormatFeatureFlagBits -> FormatFeatureFlagBits -> IO ()
$cpoke :: Ptr FormatFeatureFlagBits -> FormatFeatureFlagBits -> IO ()
peek :: Ptr FormatFeatureFlagBits -> IO FormatFeatureFlagBits
$cpeek :: Ptr FormatFeatureFlagBits -> IO FormatFeatureFlagBits
pokeByteOff :: Ptr b -> Int -> FormatFeatureFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> FormatFeatureFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO FormatFeatureFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO FormatFeatureFlagBits
pokeElemOff :: Ptr FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits -> IO ()
$cpokeElemOff :: Ptr FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits -> IO ()
peekElemOff :: Ptr FormatFeatureFlagBits -> Int -> IO FormatFeatureFlagBits
$cpeekElemOff :: Ptr FormatFeatureFlagBits -> Int -> IO FormatFeatureFlagBits
alignment :: FormatFeatureFlagBits -> Int
$calignment :: FormatFeatureFlagBits -> Int
sizeOf :: FormatFeatureFlagBits -> Int
$csizeOf :: FormatFeatureFlagBits -> Int
Storable, FormatFeatureFlagBits
FormatFeatureFlagBits -> Zero FormatFeatureFlagBits
forall a. a -> Zero a
zero :: FormatFeatureFlagBits
$czero :: FormatFeatureFlagBits
Zero, Eq FormatFeatureFlagBits
FormatFeatureFlagBits
Eq FormatFeatureFlagBits =>
(FormatFeatureFlagBits
 -> FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits
    -> FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits
    -> FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> FormatFeatureFlagBits
-> (Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> Bool)
-> (FormatFeatureFlagBits -> Maybe Int)
-> (FormatFeatureFlagBits -> Int)
-> (FormatFeatureFlagBits -> Bool)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits)
-> (FormatFeatureFlagBits -> Int)
-> Bits FormatFeatureFlagBits
Int -> FormatFeatureFlagBits
FormatFeatureFlagBits -> Bool
FormatFeatureFlagBits -> Int
FormatFeatureFlagBits -> Maybe Int
FormatFeatureFlagBits -> FormatFeatureFlagBits
FormatFeatureFlagBits -> Int -> Bool
FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: FormatFeatureFlagBits -> Int
$cpopCount :: FormatFeatureFlagBits -> Int
rotateR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$crotateR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
rotateL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$crotateL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
unsafeShiftR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cunsafeShiftR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
shiftR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cshiftR :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
unsafeShiftL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cunsafeShiftL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
shiftL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cshiftL :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
isSigned :: FormatFeatureFlagBits -> Bool
$cisSigned :: FormatFeatureFlagBits -> Bool
bitSize :: FormatFeatureFlagBits -> Int
$cbitSize :: FormatFeatureFlagBits -> Int
bitSizeMaybe :: FormatFeatureFlagBits -> Maybe Int
$cbitSizeMaybe :: FormatFeatureFlagBits -> Maybe Int
testBit :: FormatFeatureFlagBits -> Int -> Bool
$ctestBit :: FormatFeatureFlagBits -> Int -> Bool
complementBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$ccomplementBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
clearBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cclearBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
setBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$csetBit :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
bit :: Int -> FormatFeatureFlagBits
$cbit :: Int -> FormatFeatureFlagBits
zeroBits :: FormatFeatureFlagBits
$czeroBits :: FormatFeatureFlagBits
rotate :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$crotate :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
shift :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
$cshift :: FormatFeatureFlagBits -> Int -> FormatFeatureFlagBits
complement :: FormatFeatureFlagBits -> FormatFeatureFlagBits
$ccomplement :: FormatFeatureFlagBits -> FormatFeatureFlagBits
xor :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$cxor :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
.|. :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$c.|. :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
.&. :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$c.&. :: FormatFeatureFlagBits
-> FormatFeatureFlagBits -> FormatFeatureFlagBits
$cp1Bits :: Eq FormatFeatureFlagBits
Bits)

-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' specifies that an image view /can/ be
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-sampledimage sampled from>.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_BIT = FormatFeatureFlagBits 0x00000001
-- | 'FORMAT_FEATURE_STORAGE_IMAGE_BIT' specifies that an image view /can/ be
-- used as a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-storageimage storage images>.
pattern $bFORMAT_FEATURE_STORAGE_IMAGE_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_STORAGE_IMAGE_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_STORAGE_IMAGE_BIT = FormatFeatureFlagBits 0x00000002
-- | 'FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' specifies that an image view
-- /can/ be used as storage image that supports atomic operations.
pattern $bFORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT = FormatFeatureFlagBits 0x00000004
-- | 'FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT' specifies that the format
-- /can/ be used to create a buffer view that /can/ be bound to a
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
-- descriptor.
pattern $bFORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT = FormatFeatureFlagBits 0x00000008
-- | 'FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT' specifies that the format
-- /can/ be used to create a buffer view that /can/ be bound to a
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
-- descriptor.
pattern $bFORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT = FormatFeatureFlagBits 0x00000010
-- | 'FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' specifies that atomic
-- operations are supported on
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
-- with this format.
pattern $bFORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT = FormatFeatureFlagBits 0x00000020
-- | 'FORMAT_FEATURE_VERTEX_BUFFER_BIT' specifies that the format /can/ be
-- used as a vertex attribute format
-- ('Vulkan.Core10.Pipeline.VertexInputAttributeDescription'::@format@).
pattern $bFORMAT_FEATURE_VERTEX_BUFFER_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_VERTEX_BUFFER_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_VERTEX_BUFFER_BIT = FormatFeatureFlagBits 0x00000040
-- | 'FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' specifies that an image view /can/
-- be used as a framebuffer color attachment and as an input attachment.
pattern $bFORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_COLOR_ATTACHMENT_BIT = FormatFeatureFlagBits 0x00000080
-- | 'FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT' specifies that an image view
-- /can/ be used as a framebuffer color attachment that supports blending
-- and as an input attachment.
pattern $bFORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT = FormatFeatureFlagBits 0x00000100
-- | 'FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' specifies that an image
-- view /can/ be used as a framebuffer depth\/stencil attachment and as an
-- input attachment.
pattern $bFORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT = FormatFeatureFlagBits 0x00000200
-- | 'FORMAT_FEATURE_BLIT_SRC_BIT' specifies that an image /can/ be used as
-- @srcImage@ for the
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR' and
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' commands.
pattern $bFORMAT_FEATURE_BLIT_SRC_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_BLIT_SRC_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_BLIT_SRC_BIT = FormatFeatureFlagBits 0x00000400
-- | 'FORMAT_FEATURE_BLIT_DST_BIT' specifies that an image /can/ be used as
-- @dstImage@ for the
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR' and
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' commands.
pattern $bFORMAT_FEATURE_BLIT_DST_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_BLIT_DST_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_BLIT_DST_BIT = FormatFeatureFlagBits 0x00000800
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' specifies that if
-- 'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' is also set, an image view /can/ be
-- used with a sampler that has either of @magFilter@ or @minFilter@ set to
-- 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR', or @mipmapMode@ set to
-- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_LINEAR'. If
-- 'FORMAT_FEATURE_BLIT_SRC_BIT' is also set, an image can be used as the
-- @srcImage@ to 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR'
-- and 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage' with a @filter@
-- of 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR'. This bit /must/ only be
-- exposed for formats that also support the
-- 'FORMAT_FEATURE_SAMPLED_IMAGE_BIT' or 'FORMAT_FEATURE_BLIT_SRC_BIT'.
--
-- If the format being queried is a depth\/stencil format, this bit only
-- specifies that the depth aspect (not the stencil aspect) of an image of
-- this format supports linear filtering, and that linear filtering of the
-- depth aspect is supported whether depth compare is enabled in the
-- sampler or not. If this bit is not present, linear filtering with depth
-- compare disabled is unsupported and linear filtering with depth compare
-- enabled is supported, but /may/ compute the filtered value in an
-- implementation-dependent manner which differs from the normal rules of
-- linear filtering. The resulting value /must/ be in the range [0,1] and
-- /should/ be proportional to, or a weighted average of, the number of
-- comparison passes or failures.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT = FormatFeatureFlagBits 0x00001000
-- | 'FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' specifies that
-- an image view /can/ be used as a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment>.
-- An implementation /must/ not set this feature for formats that with
-- numeric type other than @*UINT@, or set it as a buffer feature.
pattern $bFORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: FormatFeatureFlagBits
$mFORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR = FormatFeatureFlagBits 0x40000000
-- | 'FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT' specifies that an image
-- view /can/ be used as a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-fragmentdensitymapattachment fragment density map attachment>.
pattern $bFORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT = FormatFeatureFlagBits 0x01000000
-- No documentation found for Nested "VkFormatFeatureFlagBits" "VK_FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR"
pattern $bFORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR :: FormatFeatureFlagBits
$mFORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR = FormatFeatureFlagBits 0x20000000
-- No documentation found for Nested "VkFormatFeatureFlagBits" "VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG"
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG = FormatFeatureFlagBits 0x00002000
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT' specifies
-- 'Vulkan.Core10.Handles.Image' /can/ be used as a sampled image with a
-- min or max
-- 'Vulkan.Core12.Enums.SamplerReductionMode.SamplerReductionMode'. This
-- bit /must/ only be exposed for formats that also support the
-- 'FORMAT_FEATURE_SAMPLED_IMAGE_BIT'.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT = FormatFeatureFlagBits 0x00010000
-- | 'FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT' specifies that an
-- application /can/ define a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
-- using this format as a source, and that an image of this format /can/ be
-- used with a
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'
-- @xChromaOffset@ and\/or @yChromaOffset@ of
-- 'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_COSITED_EVEN'.
-- Otherwise both @xChromaOffset@ and @yChromaOffset@ /must/ be
-- 'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_MIDPOINT'. If
-- neither 'FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT' nor
-- 'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT' is set, the application
-- /must/ not define a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
-- using this format as a source.
pattern $bFORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT = FormatFeatureFlagBits 0x00800000
-- | 'FORMAT_FEATURE_DISJOINT_BIT' specifies that a multi-planar image /can/
-- have the
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_DISJOINT_BIT' set
-- during image creation. An implementation /must/ not set
-- 'FORMAT_FEATURE_DISJOINT_BIT' for /single-plane formats/.
pattern $bFORMAT_FEATURE_DISJOINT_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_DISJOINT_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_DISJOINT_BIT = FormatFeatureFlagBits 0x00400000
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT'
-- specifies that reconstruction /can/ be forcibly made explicit by setting
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'::@forceExplicitReconstruction@
-- to 'Vulkan.Core10.FundamentalTypes.TRUE'. If the format being queried
-- supports
-- 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT'
-- it /must/ also support
-- 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT'.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT = FormatFeatureFlagBits 0x00200000
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT'
-- specifies that reconstruction is explicit, as described in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-chroma-reconstruction>.
-- If this bit is not present, reconstruction is implicit by default.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT = FormatFeatureFlagBits 0x00100000
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT'
-- specifies that the format can have different chroma, min, and mag
-- filters.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT = FormatFeatureFlagBits 0x00080000
-- | 'FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT'
-- specifies that the format can do linear sampler filtering
-- (min\/magFilter) whilst sampler Y′CBCR conversion is enabled.
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT = FormatFeatureFlagBits 0x00040000
-- | 'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT' specifies that an
-- application /can/ define a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
-- using this format as a source, and that an image of this format /can/ be
-- used with a
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'
-- @xChromaOffset@ and\/or @yChromaOffset@ of
-- 'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_MIDPOINT'. Otherwise
-- both @xChromaOffset@ and @yChromaOffset@ /must/ be
-- 'Vulkan.Core11.Enums.ChromaLocation.CHROMA_LOCATION_COSITED_EVEN'. If a
-- format does not incorporate chroma downsampling (it is not a “422” or
-- “420” format) but the implementation supports sampler Y′CBCR conversion
-- for this format, the implementation /must/ set
-- 'FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT'.
pattern $bFORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT = FormatFeatureFlagBits 0x00020000
-- | 'FORMAT_FEATURE_TRANSFER_DST_BIT' specifies that an image /can/ be used
-- as a destination image for
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies copy commands>
-- and
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears clear commands>.
pattern $bFORMAT_FEATURE_TRANSFER_DST_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_TRANSFER_DST_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_TRANSFER_DST_BIT = FormatFeatureFlagBits 0x00008000
-- | 'FORMAT_FEATURE_TRANSFER_SRC_BIT' specifies that an image /can/ be used
-- as a source image for
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies copy commands>.
pattern $bFORMAT_FEATURE_TRANSFER_SRC_BIT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_TRANSFER_SRC_BIT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_TRANSFER_SRC_BIT = FormatFeatureFlagBits 0x00004000

type FormatFeatureFlags = FormatFeatureFlagBits

instance Show FormatFeatureFlagBits where
  showsPrec :: Int -> FormatFeatureFlagBits -> ShowS
showsPrec p :: Int
p = \case
    FORMAT_FEATURE_SAMPLED_IMAGE_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_BIT"
    FORMAT_FEATURE_STORAGE_IMAGE_BIT -> String -> ShowS
showString "FORMAT_FEATURE_STORAGE_IMAGE_BIT"
    FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT -> String -> ShowS
showString "FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT"
    FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT -> String -> ShowS
showString "FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT"
    FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT -> String -> ShowS
showString "FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT"
    FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT -> String -> ShowS
showString "FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT"
    FORMAT_FEATURE_VERTEX_BUFFER_BIT -> String -> ShowS
showString "FORMAT_FEATURE_VERTEX_BUFFER_BIT"
    FORMAT_FEATURE_COLOR_ATTACHMENT_BIT -> String -> ShowS
showString "FORMAT_FEATURE_COLOR_ATTACHMENT_BIT"
    FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT -> String -> ShowS
showString "FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT"
    FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT -> String -> ShowS
showString "FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT"
    FORMAT_FEATURE_BLIT_SRC_BIT -> String -> ShowS
showString "FORMAT_FEATURE_BLIT_SRC_BIT"
    FORMAT_FEATURE_BLIT_DST_BIT -> String -> ShowS
showString "FORMAT_FEATURE_BLIT_DST_BIT"
    FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT"
    FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR -> String -> ShowS
showString "FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR"
    FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT -> String -> ShowS
showString "FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT"
    FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR -> String -> ShowS
showString "FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR"
    FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG"
    FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT"
    FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT -> String -> ShowS
showString "FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT"
    FORMAT_FEATURE_DISJOINT_BIT -> String -> ShowS
showString "FORMAT_FEATURE_DISJOINT_BIT"
    FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT"
    FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT"
    FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT"
    FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT -> String -> ShowS
showString "FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT"
    FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT -> String -> ShowS
showString "FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT"
    FORMAT_FEATURE_TRANSFER_DST_BIT -> String -> ShowS
showString "FORMAT_FEATURE_TRANSFER_DST_BIT"
    FORMAT_FEATURE_TRANSFER_SRC_BIT -> String -> ShowS
showString "FORMAT_FEATURE_TRANSFER_SRC_BIT"
    FormatFeatureFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "FormatFeatureFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read FormatFeatureFlagBits where
  readPrec :: ReadPrec FormatFeatureFlagBits
readPrec = ReadPrec FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec FormatFeatureFlagBits)]
-> ReadPrec FormatFeatureFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("FORMAT_FEATURE_SAMPLED_IMAGE_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_BIT)
                            , ("FORMAT_FEATURE_STORAGE_IMAGE_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_STORAGE_IMAGE_BIT)
                            , ("FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT)
                            , ("FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT)
                            , ("FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT)
                            , ("FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT)
                            , ("FORMAT_FEATURE_VERTEX_BUFFER_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_VERTEX_BUFFER_BIT)
                            , ("FORMAT_FEATURE_COLOR_ATTACHMENT_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_COLOR_ATTACHMENT_BIT)
                            , ("FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT)
                            , ("FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT)
                            , ("FORMAT_FEATURE_BLIT_SRC_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_BLIT_SRC_BIT)
                            , ("FORMAT_FEATURE_BLIT_DST_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_BLIT_DST_BIT)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT)
                            , ("FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR)
                            , ("FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT)
                            , ("FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT)
                            , ("FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT)
                            , ("FORMAT_FEATURE_DISJOINT_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_DISJOINT_BIT)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT)
                            , ("FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT)
                            , ("FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT)
                            , ("FORMAT_FEATURE_TRANSFER_DST_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_TRANSFER_DST_BIT)
                            , ("FORMAT_FEATURE_TRANSFER_SRC_BIT", FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatFeatureFlagBits
FORMAT_FEATURE_TRANSFER_SRC_BIT)]
                     ReadPrec FormatFeatureFlagBits
-> ReadPrec FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "FormatFeatureFlagBits")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       FormatFeatureFlagBits -> ReadPrec FormatFeatureFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> FormatFeatureFlagBits
FormatFeatureFlagBits Flags
v)))