{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Format
       (VkFormat(VkFormat, VK_FORMAT_UNDEFINED,
                 VK_FORMAT_R4G4_UNORM_PACK8, VK_FORMAT_R4G4B4A4_UNORM_PACK16,
                 VK_FORMAT_B4G4R4A4_UNORM_PACK16, VK_FORMAT_R5G6B5_UNORM_PACK16,
                 VK_FORMAT_B5G6R5_UNORM_PACK16, VK_FORMAT_R5G5B5A1_UNORM_PACK16,
                 VK_FORMAT_B5G5R5A1_UNORM_PACK16, VK_FORMAT_A1R5G5B5_UNORM_PACK16,
                 VK_FORMAT_R8_UNORM, VK_FORMAT_R8_SNORM, VK_FORMAT_R8_USCALED,
                 VK_FORMAT_R8_SSCALED, VK_FORMAT_R8_UINT, VK_FORMAT_R8_SINT,
                 VK_FORMAT_R8_SRGB, VK_FORMAT_R8G8_UNORM, VK_FORMAT_R8G8_SNORM,
                 VK_FORMAT_R8G8_USCALED, VK_FORMAT_R8G8_SSCALED,
                 VK_FORMAT_R8G8_UINT, VK_FORMAT_R8G8_SINT, VK_FORMAT_R8G8_SRGB,
                 VK_FORMAT_R8G8B8_UNORM, VK_FORMAT_R8G8B8_SNORM,
                 VK_FORMAT_R8G8B8_USCALED, VK_FORMAT_R8G8B8_SSCALED,
                 VK_FORMAT_R8G8B8_UINT, VK_FORMAT_R8G8B8_SINT,
                 VK_FORMAT_R8G8B8_SRGB, VK_FORMAT_B8G8R8_UNORM,
                 VK_FORMAT_B8G8R8_SNORM, VK_FORMAT_B8G8R8_USCALED,
                 VK_FORMAT_B8G8R8_SSCALED, VK_FORMAT_B8G8R8_UINT,
                 VK_FORMAT_B8G8R8_SINT, VK_FORMAT_B8G8R8_SRGB,
                 VK_FORMAT_R8G8B8A8_UNORM, VK_FORMAT_R8G8B8A8_SNORM,
                 VK_FORMAT_R8G8B8A8_USCALED, VK_FORMAT_R8G8B8A8_SSCALED,
                 VK_FORMAT_R8G8B8A8_UINT, VK_FORMAT_R8G8B8A8_SINT,
                 VK_FORMAT_R8G8B8A8_SRGB, VK_FORMAT_B8G8R8A8_UNORM,
                 VK_FORMAT_B8G8R8A8_SNORM, VK_FORMAT_B8G8R8A8_USCALED,
                 VK_FORMAT_B8G8R8A8_SSCALED, VK_FORMAT_B8G8R8A8_UINT,
                 VK_FORMAT_B8G8R8A8_SINT, VK_FORMAT_B8G8R8A8_SRGB,
                 VK_FORMAT_A8B8G8R8_UNORM_PACK32, VK_FORMAT_A8B8G8R8_SNORM_PACK32,
                 VK_FORMAT_A8B8G8R8_USCALED_PACK32,
                 VK_FORMAT_A8B8G8R8_SSCALED_PACK32, VK_FORMAT_A8B8G8R8_UINT_PACK32,
                 VK_FORMAT_A8B8G8R8_SINT_PACK32, VK_FORMAT_A8B8G8R8_SRGB_PACK32,
                 VK_FORMAT_A2R10G10B10_UNORM_PACK32,
                 VK_FORMAT_A2R10G10B10_SNORM_PACK32,
                 VK_FORMAT_A2R10G10B10_USCALED_PACK32,
                 VK_FORMAT_A2R10G10B10_SSCALED_PACK32,
                 VK_FORMAT_A2R10G10B10_UINT_PACK32,
                 VK_FORMAT_A2R10G10B10_SINT_PACK32,
                 VK_FORMAT_A2B10G10R10_UNORM_PACK32,
                 VK_FORMAT_A2B10G10R10_SNORM_PACK32,
                 VK_FORMAT_A2B10G10R10_USCALED_PACK32,
                 VK_FORMAT_A2B10G10R10_SSCALED_PACK32,
                 VK_FORMAT_A2B10G10R10_UINT_PACK32,
                 VK_FORMAT_A2B10G10R10_SINT_PACK32, VK_FORMAT_R16_UNORM,
                 VK_FORMAT_R16_SNORM, VK_FORMAT_R16_USCALED, VK_FORMAT_R16_SSCALED,
                 VK_FORMAT_R16_UINT, VK_FORMAT_R16_SINT, VK_FORMAT_R16_SFLOAT,
                 VK_FORMAT_R16G16_UNORM, VK_FORMAT_R16G16_SNORM,
                 VK_FORMAT_R16G16_USCALED, VK_FORMAT_R16G16_SSCALED,
                 VK_FORMAT_R16G16_UINT, VK_FORMAT_R16G16_SINT,
                 VK_FORMAT_R16G16_SFLOAT, VK_FORMAT_R16G16B16_UNORM,
                 VK_FORMAT_R16G16B16_SNORM, VK_FORMAT_R16G16B16_USCALED,
                 VK_FORMAT_R16G16B16_SSCALED, VK_FORMAT_R16G16B16_UINT,
                 VK_FORMAT_R16G16B16_SINT, VK_FORMAT_R16G16B16_SFLOAT,
                 VK_FORMAT_R16G16B16A16_UNORM, VK_FORMAT_R16G16B16A16_SNORM,
                 VK_FORMAT_R16G16B16A16_USCALED, VK_FORMAT_R16G16B16A16_SSCALED,
                 VK_FORMAT_R16G16B16A16_UINT, VK_FORMAT_R16G16B16A16_SINT,
                 VK_FORMAT_R16G16B16A16_SFLOAT, VK_FORMAT_R32_UINT,
                 VK_FORMAT_R32_SINT, VK_FORMAT_R32_SFLOAT, VK_FORMAT_R32G32_UINT,
                 VK_FORMAT_R32G32_SINT, VK_FORMAT_R32G32_SFLOAT,
                 VK_FORMAT_R32G32B32_UINT, VK_FORMAT_R32G32B32_SINT,
                 VK_FORMAT_R32G32B32_SFLOAT, VK_FORMAT_R32G32B32A32_UINT,
                 VK_FORMAT_R32G32B32A32_SINT, VK_FORMAT_R32G32B32A32_SFLOAT,
                 VK_FORMAT_R64_UINT, VK_FORMAT_R64_SINT, VK_FORMAT_R64_SFLOAT,
                 VK_FORMAT_R64G64_UINT, VK_FORMAT_R64G64_SINT,
                 VK_FORMAT_R64G64_SFLOAT, VK_FORMAT_R64G64B64_UINT,
                 VK_FORMAT_R64G64B64_SINT, VK_FORMAT_R64G64B64_SFLOAT,
                 VK_FORMAT_R64G64B64A64_UINT, VK_FORMAT_R64G64B64A64_SINT,
                 VK_FORMAT_R64G64B64A64_SFLOAT, VK_FORMAT_B10G11R11_UFLOAT_PACK32,
                 VK_FORMAT_E5B9G9R9_UFLOAT_PACK32, VK_FORMAT_D16_UNORM,
                 VK_FORMAT_X8_D24_UNORM_PACK32, VK_FORMAT_D32_SFLOAT,
                 VK_FORMAT_S8_UINT, VK_FORMAT_D16_UNORM_S8_UINT,
                 VK_FORMAT_D24_UNORM_S8_UINT, VK_FORMAT_D32_SFLOAT_S8_UINT,
                 VK_FORMAT_BC1_RGB_UNORM_BLOCK, VK_FORMAT_BC1_RGB_SRGB_BLOCK,
                 VK_FORMAT_BC1_RGBA_UNORM_BLOCK, VK_FORMAT_BC1_RGBA_SRGB_BLOCK,
                 VK_FORMAT_BC2_UNORM_BLOCK, VK_FORMAT_BC2_SRGB_BLOCK,
                 VK_FORMAT_BC3_UNORM_BLOCK, VK_FORMAT_BC3_SRGB_BLOCK,
                 VK_FORMAT_BC4_UNORM_BLOCK, VK_FORMAT_BC4_SNORM_BLOCK,
                 VK_FORMAT_BC5_UNORM_BLOCK, VK_FORMAT_BC5_SNORM_BLOCK,
                 VK_FORMAT_BC6H_UFLOAT_BLOCK, VK_FORMAT_BC6H_SFLOAT_BLOCK,
                 VK_FORMAT_BC7_UNORM_BLOCK, VK_FORMAT_BC7_SRGB_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK,
                 VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK, VK_FORMAT_EAC_R11_UNORM_BLOCK,
                 VK_FORMAT_EAC_R11_SNORM_BLOCK, VK_FORMAT_EAC_R11G11_UNORM_BLOCK,
                 VK_FORMAT_EAC_R11G11_SNORM_BLOCK, VK_FORMAT_ASTC_4x4_UNORM_BLOCK,
                 VK_FORMAT_ASTC_4x4_SRGB_BLOCK, VK_FORMAT_ASTC_5x4_UNORM_BLOCK,
                 VK_FORMAT_ASTC_5x4_SRGB_BLOCK, VK_FORMAT_ASTC_5x5_UNORM_BLOCK,
                 VK_FORMAT_ASTC_5x5_SRGB_BLOCK, VK_FORMAT_ASTC_6x5_UNORM_BLOCK,
                 VK_FORMAT_ASTC_6x5_SRGB_BLOCK, VK_FORMAT_ASTC_6x6_UNORM_BLOCK,
                 VK_FORMAT_ASTC_6x6_SRGB_BLOCK, VK_FORMAT_ASTC_8x5_UNORM_BLOCK,
                 VK_FORMAT_ASTC_8x5_SRGB_BLOCK, VK_FORMAT_ASTC_8x6_UNORM_BLOCK,
                 VK_FORMAT_ASTC_8x6_SRGB_BLOCK, VK_FORMAT_ASTC_8x8_UNORM_BLOCK,
                 VK_FORMAT_ASTC_8x8_SRGB_BLOCK, VK_FORMAT_ASTC_10x5_UNORM_BLOCK,
                 VK_FORMAT_ASTC_10x5_SRGB_BLOCK, VK_FORMAT_ASTC_10x6_UNORM_BLOCK,
                 VK_FORMAT_ASTC_10x6_SRGB_BLOCK, VK_FORMAT_ASTC_10x8_UNORM_BLOCK,
                 VK_FORMAT_ASTC_10x8_SRGB_BLOCK, VK_FORMAT_ASTC_10x10_UNORM_BLOCK,
                 VK_FORMAT_ASTC_10x10_SRGB_BLOCK, VK_FORMAT_ASTC_12x10_UNORM_BLOCK,
                 VK_FORMAT_ASTC_12x10_SRGB_BLOCK, VK_FORMAT_ASTC_12x12_UNORM_BLOCK,
                 VK_FORMAT_ASTC_12x12_SRGB_BLOCK),
        VkFormatFeatureBitmask(VkFormatFeatureBitmask,
                               VkFormatFeatureFlags, VkFormatFeatureFlagBits,
                               VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT,
                               VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT,
                               VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT,
                               VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT,
                               VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT,
                               VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT,
                               VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT,
                               VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT,
                               VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT,
                               VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT,
                               VK_FORMAT_FEATURE_BLIT_SRC_BIT, VK_FORMAT_FEATURE_BLIT_DST_BIT,
                               VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT),
        VkFormatFeatureFlags, VkFormatFeatureFlagBits)
       where
import           Data.Bits                       (Bits, FiniteBits)
import           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
import           GHC.Read                        (choose, expectP)
import           Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType,
                                                  Int32)
import           Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import           Text.ParserCombinators.ReadPrec (prec, step, (+++))
import           Text.Read                       (Read (..), parens)
import           Text.Read.Lex                   (Lexeme (..))

-- | Vulkan format definitions
--
--   type = @enum@
--
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkFormat VkFormat registry at www.khronos.org>
newtype VkFormat = VkFormat Int32
                     deriving (VkFormat -> VkFormat -> Bool
(VkFormat -> VkFormat -> Bool)
-> (VkFormat -> VkFormat -> Bool) -> Eq VkFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkFormat -> VkFormat -> Bool
$c/= :: VkFormat -> VkFormat -> Bool
== :: VkFormat -> VkFormat -> Bool
$c== :: VkFormat -> VkFormat -> Bool
Eq, Eq VkFormat
Eq VkFormat
-> (VkFormat -> VkFormat -> Ordering)
-> (VkFormat -> VkFormat -> Bool)
-> (VkFormat -> VkFormat -> Bool)
-> (VkFormat -> VkFormat -> Bool)
-> (VkFormat -> VkFormat -> Bool)
-> (VkFormat -> VkFormat -> VkFormat)
-> (VkFormat -> VkFormat -> VkFormat)
-> Ord VkFormat
VkFormat -> VkFormat -> Bool
VkFormat -> VkFormat -> Ordering
VkFormat -> VkFormat -> VkFormat
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 :: VkFormat -> VkFormat -> VkFormat
$cmin :: VkFormat -> VkFormat -> VkFormat
max :: VkFormat -> VkFormat -> VkFormat
$cmax :: VkFormat -> VkFormat -> VkFormat
>= :: VkFormat -> VkFormat -> Bool
$c>= :: VkFormat -> VkFormat -> Bool
> :: VkFormat -> VkFormat -> Bool
$c> :: VkFormat -> VkFormat -> Bool
<= :: VkFormat -> VkFormat -> Bool
$c<= :: VkFormat -> VkFormat -> Bool
< :: VkFormat -> VkFormat -> Bool
$c< :: VkFormat -> VkFormat -> Bool
compare :: VkFormat -> VkFormat -> Ordering
$ccompare :: VkFormat -> VkFormat -> Ordering
$cp1Ord :: Eq VkFormat
Ord, Integer -> VkFormat
VkFormat -> VkFormat
VkFormat -> VkFormat -> VkFormat
(VkFormat -> VkFormat -> VkFormat)
-> (VkFormat -> VkFormat -> VkFormat)
-> (VkFormat -> VkFormat -> VkFormat)
-> (VkFormat -> VkFormat)
-> (VkFormat -> VkFormat)
-> (VkFormat -> VkFormat)
-> (Integer -> VkFormat)
-> Num VkFormat
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkFormat
$cfromInteger :: Integer -> VkFormat
signum :: VkFormat -> VkFormat
$csignum :: VkFormat -> VkFormat
abs :: VkFormat -> VkFormat
$cabs :: VkFormat -> VkFormat
negate :: VkFormat -> VkFormat
$cnegate :: VkFormat -> VkFormat
* :: VkFormat -> VkFormat -> VkFormat
$c* :: VkFormat -> VkFormat -> VkFormat
- :: VkFormat -> VkFormat -> VkFormat
$c- :: VkFormat -> VkFormat -> VkFormat
+ :: VkFormat -> VkFormat -> VkFormat
$c+ :: VkFormat -> VkFormat -> VkFormat
Num, VkFormat
VkFormat -> VkFormat -> Bounded VkFormat
forall a. a -> a -> Bounded a
maxBound :: VkFormat
$cmaxBound :: VkFormat
minBound :: VkFormat
$cminBound :: VkFormat
Bounded, Ptr b -> Int -> IO VkFormat
Ptr b -> Int -> VkFormat -> IO ()
Ptr VkFormat -> IO VkFormat
Ptr VkFormat -> Int -> IO VkFormat
Ptr VkFormat -> Int -> VkFormat -> IO ()
Ptr VkFormat -> VkFormat -> IO ()
VkFormat -> Int
(VkFormat -> Int)
-> (VkFormat -> Int)
-> (Ptr VkFormat -> Int -> IO VkFormat)
-> (Ptr VkFormat -> Int -> VkFormat -> IO ())
-> (forall b. Ptr b -> Int -> IO VkFormat)
-> (forall b. Ptr b -> Int -> VkFormat -> IO ())
-> (Ptr VkFormat -> IO VkFormat)
-> (Ptr VkFormat -> VkFormat -> IO ())
-> Storable VkFormat
forall b. Ptr b -> Int -> IO VkFormat
forall b. Ptr b -> Int -> VkFormat -> 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 VkFormat -> VkFormat -> IO ()
$cpoke :: Ptr VkFormat -> VkFormat -> IO ()
peek :: Ptr VkFormat -> IO VkFormat
$cpeek :: Ptr VkFormat -> IO VkFormat
pokeByteOff :: Ptr b -> Int -> VkFormat -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkFormat -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkFormat
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkFormat
pokeElemOff :: Ptr VkFormat -> Int -> VkFormat -> IO ()
$cpokeElemOff :: Ptr VkFormat -> Int -> VkFormat -> IO ()
peekElemOff :: Ptr VkFormat -> Int -> IO VkFormat
$cpeekElemOff :: Ptr VkFormat -> Int -> IO VkFormat
alignment :: VkFormat -> Int
$calignment :: VkFormat -> Int
sizeOf :: VkFormat -> Int
$csizeOf :: VkFormat -> Int
Storable, Int -> VkFormat
VkFormat -> Int
VkFormat -> [VkFormat]
VkFormat -> VkFormat
VkFormat -> VkFormat -> [VkFormat]
VkFormat -> VkFormat -> VkFormat -> [VkFormat]
(VkFormat -> VkFormat)
-> (VkFormat -> VkFormat)
-> (Int -> VkFormat)
-> (VkFormat -> Int)
-> (VkFormat -> [VkFormat])
-> (VkFormat -> VkFormat -> [VkFormat])
-> (VkFormat -> VkFormat -> [VkFormat])
-> (VkFormat -> VkFormat -> VkFormat -> [VkFormat])
-> Enum VkFormat
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkFormat -> VkFormat -> VkFormat -> [VkFormat]
$cenumFromThenTo :: VkFormat -> VkFormat -> VkFormat -> [VkFormat]
enumFromTo :: VkFormat -> VkFormat -> [VkFormat]
$cenumFromTo :: VkFormat -> VkFormat -> [VkFormat]
enumFromThen :: VkFormat -> VkFormat -> [VkFormat]
$cenumFromThen :: VkFormat -> VkFormat -> [VkFormat]
enumFrom :: VkFormat -> [VkFormat]
$cenumFrom :: VkFormat -> [VkFormat]
fromEnum :: VkFormat -> Int
$cfromEnum :: VkFormat -> Int
toEnum :: Int -> VkFormat
$ctoEnum :: Int -> VkFormat
pred :: VkFormat -> VkFormat
$cpred :: VkFormat -> VkFormat
succ :: VkFormat -> VkFormat
$csucc :: VkFormat -> VkFormat
Enum, Typeable VkFormat
DataType
Constr
Typeable VkFormat
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> VkFormat -> c VkFormat)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkFormat)
-> (VkFormat -> Constr)
-> (VkFormat -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VkFormat))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat))
-> ((forall b. Data b => b -> b) -> VkFormat -> VkFormat)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VkFormat -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VkFormat -> r)
-> (forall u. (forall d. Data d => d -> u) -> VkFormat -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> VkFormat -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat)
-> Data VkFormat
VkFormat -> DataType
VkFormat -> Constr
(forall b. Data b => b -> b) -> VkFormat -> VkFormat
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFormat -> c VkFormat
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFormat
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VkFormat -> u
forall u. (forall d. Data d => d -> u) -> VkFormat -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFormat
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFormat -> c VkFormat
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkFormat)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat)
$cVkFormat :: Constr
$tVkFormat :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
gmapMp :: (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
gmapM :: (forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkFormat -> m VkFormat
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkFormat -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VkFormat -> u
gmapQ :: (forall d. Data d => d -> u) -> VkFormat -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VkFormat -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkFormat -> r
gmapT :: (forall b. Data b => b -> b) -> VkFormat -> VkFormat
$cgmapT :: (forall b. Data b => b -> b) -> VkFormat -> VkFormat
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VkFormat)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkFormat)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkFormat)
dataTypeOf :: VkFormat -> DataType
$cdataTypeOf :: VkFormat -> DataType
toConstr :: VkFormat -> Constr
$ctoConstr :: VkFormat -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFormat
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkFormat
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFormat -> c VkFormat
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkFormat -> c VkFormat
$cp1Data :: Typeable VkFormat
Data, (forall x. VkFormat -> Rep VkFormat x)
-> (forall x. Rep VkFormat x -> VkFormat) -> Generic VkFormat
forall x. Rep VkFormat x -> VkFormat
forall x. VkFormat -> Rep VkFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VkFormat x -> VkFormat
$cfrom :: forall x. VkFormat -> Rep VkFormat x
Generic)

instance Show VkFormat where
        showsPrec :: Int -> VkFormat -> ShowS
showsPrec Int
_ VkFormat
VK_FORMAT_UNDEFINED = String -> ShowS
showString String
"VK_FORMAT_UNDEFINED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R4G4_UNORM_PACK8
          = String -> ShowS
showString String
"VK_FORMAT_R4G4_UNORM_PACK8"
        showsPrec Int
_ VkFormat
VK_FORMAT_R4G4B4A4_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_R4G4B4A4_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_B4G4R4A4_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_B4G4R4A4_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_R5G6B5_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_R5G6B5_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_B5G6R5_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_B5G6R5_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_R5G5B5A1_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_R5G5B5A1_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_B5G5R5A1_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_B5G5R5A1_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_A1R5G5B5_UNORM_PACK16
          = String -> ShowS
showString String
"VK_FORMAT_A1R5G5B5_UNORM_PACK16"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_UNORM = String -> ShowS
showString String
"VK_FORMAT_R8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_SNORM = String -> ShowS
showString String
"VK_FORMAT_R8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_UINT = String -> ShowS
showString String
"VK_FORMAT_R8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_SINT = String -> ShowS
showString String
"VK_FORMAT_R8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8_SRGB = String -> ShowS
showString String
"VK_FORMAT_R8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_UINT = String -> ShowS
showString String
"VK_FORMAT_R8G8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_SINT = String -> ShowS
showString String
"VK_FORMAT_R8G8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8_SRGB = String -> ShowS
showString String
"VK_FORMAT_R8G8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8_SRGB
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_SINT
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8_SRGB
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R8G8B8A8_SRGB
          = String -> ShowS
showString String
"VK_FORMAT_R8G8B8A8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_SINT
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_B8G8R8A8_SRGB
          = String -> ShowS
showString String
"VK_FORMAT_B8G8R8A8_SRGB"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_UNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_UNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_SNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_SNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_USCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_USCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_SSCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_SSCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_UINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_UINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_SINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_SINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A8B8G8R8_SRGB_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A8B8G8R8_SRGB_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_UNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_UNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_SNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_SNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_USCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_USCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_SSCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_SSCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_UINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_UINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2R10G10B10_SINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2R10G10B10_SINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_UNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_UNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_SNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_SNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_USCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_USCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_SSCALED_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_SSCALED_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_UINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_UINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_A2B10G10R10_SINT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_A2B10G10R10_SINT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_UNORM = String -> ShowS
showString String
"VK_FORMAT_R16_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_SNORM = String -> ShowS
showString String
"VK_FORMAT_R16_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_UINT = String -> ShowS
showString String
"VK_FORMAT_R16_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_SINT = String -> ShowS
showString String
"VK_FORMAT_R16_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R16_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_UNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_SNORM
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_SNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_USCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_USCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_SSCALED
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_SSCALED"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R16G16B16A16_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R16G16B16A16_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32_UINT = String -> ShowS
showString String
"VK_FORMAT_R32_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32_SINT = String -> ShowS
showString String
"VK_FORMAT_R32_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R32_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32A32_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32A32_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32A32_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32A32_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R32G32B32A32_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R32G32B32A32_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64_UINT = String -> ShowS
showString String
"VK_FORMAT_R64_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64_SINT = String -> ShowS
showString String
"VK_FORMAT_R64_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R64_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64A64_UINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64A64_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64A64_SINT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64A64_SINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_R64G64B64A64_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_R64G64B64A64_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_B10G11R11_UFLOAT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_B10G11R11_UFLOAT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_E5B9G9R9_UFLOAT_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_E5B9G9R9_UFLOAT_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_D16_UNORM = String -> ShowS
showString String
"VK_FORMAT_D16_UNORM"
        showsPrec Int
_ VkFormat
VK_FORMAT_X8_D24_UNORM_PACK32
          = String -> ShowS
showString String
"VK_FORMAT_X8_D24_UNORM_PACK32"
        showsPrec Int
_ VkFormat
VK_FORMAT_D32_SFLOAT
          = String -> ShowS
showString String
"VK_FORMAT_D32_SFLOAT"
        showsPrec Int
_ VkFormat
VK_FORMAT_S8_UINT = String -> ShowS
showString String
"VK_FORMAT_S8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_D16_UNORM_S8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_D16_UNORM_S8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_D24_UNORM_S8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_D24_UNORM_S8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_D32_SFLOAT_S8_UINT
          = String -> ShowS
showString String
"VK_FORMAT_D32_SFLOAT_S8_UINT"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC1_RGB_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC1_RGB_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC1_RGB_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC1_RGB_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC1_RGBA_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC1_RGBA_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC1_RGBA_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC1_RGBA_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC2_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC2_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC2_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC2_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC3_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC3_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC3_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC3_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC4_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC4_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC4_SNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC4_SNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC5_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC5_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC5_SNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC5_SNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC6H_UFLOAT_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC6H_UFLOAT_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC6H_SFLOAT_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC6H_SFLOAT_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC7_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC7_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_BC7_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_BC7_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_EAC_R11_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_EAC_R11_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_EAC_R11_SNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_EAC_R11_SNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_EAC_R11G11_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_EAC_R11G11_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_EAC_R11G11_SNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_EAC_R11G11_SNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_4x4_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_4x4_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_4x4_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_4x4_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_5x4_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_5x4_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_5x4_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_5x4_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_5x5_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_5x5_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_5x5_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_5x5_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_6x5_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_6x5_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_6x5_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_6x5_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_6x6_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_6x6_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_6x6_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_6x6_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x5_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x5_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x5_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x5_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x6_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x6_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x6_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x6_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x8_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x8_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_8x8_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_8x8_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x5_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x5_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x5_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x5_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x6_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x6_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x6_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x6_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x8_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x8_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x8_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x8_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x10_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x10_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_10x10_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_10x10_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_12x10_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_12x10_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_12x10_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_12x10_SRGB_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_12x12_UNORM_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_12x12_UNORM_BLOCK"
        showsPrec Int
_ VkFormat
VK_FORMAT_ASTC_12x12_SRGB_BLOCK
          = String -> ShowS
showString String
"VK_FORMAT_ASTC_12x12_SRGB_BLOCK"
        showsPrec Int
p (VkFormat Int32
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"VkFormat " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkFormat where
        readPrec :: ReadPrec VkFormat
readPrec
          = ReadPrec VkFormat -> ReadPrec VkFormat
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec VkFormat)] -> ReadPrec VkFormat
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_FORMAT_UNDEFINED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_UNDEFINED),
                  (String
"VK_FORMAT_R4G4_UNORM_PACK8", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R4G4_UNORM_PACK8),
                  (String
"VK_FORMAT_R4G4B4A4_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R4G4B4A4_UNORM_PACK16),
                  (String
"VK_FORMAT_B4G4R4A4_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B4G4R4A4_UNORM_PACK16),
                  (String
"VK_FORMAT_R5G6B5_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R5G6B5_UNORM_PACK16),
                  (String
"VK_FORMAT_B5G6R5_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B5G6R5_UNORM_PACK16),
                  (String
"VK_FORMAT_R5G5B5A1_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R5G5B5A1_UNORM_PACK16),
                  (String
"VK_FORMAT_B5G5R5A1_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B5G5R5A1_UNORM_PACK16),
                  (String
"VK_FORMAT_A1R5G5B5_UNORM_PACK16",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A1R5G5B5_UNORM_PACK16),
                  (String
"VK_FORMAT_R8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_UNORM),
                  (String
"VK_FORMAT_R8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_SNORM),
                  (String
"VK_FORMAT_R8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_USCALED),
                  (String
"VK_FORMAT_R8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_SSCALED),
                  (String
"VK_FORMAT_R8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_UINT),
                  (String
"VK_FORMAT_R8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_SINT),
                  (String
"VK_FORMAT_R8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8_SRGB),
                  (String
"VK_FORMAT_R8G8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_UNORM),
                  (String
"VK_FORMAT_R8G8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_SNORM),
                  (String
"VK_FORMAT_R8G8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_USCALED),
                  (String
"VK_FORMAT_R8G8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_SSCALED),
                  (String
"VK_FORMAT_R8G8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_UINT),
                  (String
"VK_FORMAT_R8G8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_SINT),
                  (String
"VK_FORMAT_R8G8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8_SRGB),
                  (String
"VK_FORMAT_R8G8B8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_UNORM),
                  (String
"VK_FORMAT_R8G8B8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_SNORM),
                  (String
"VK_FORMAT_R8G8B8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_USCALED),
                  (String
"VK_FORMAT_R8G8B8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_SSCALED),
                  (String
"VK_FORMAT_R8G8B8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_UINT),
                  (String
"VK_FORMAT_R8G8B8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_SINT),
                  (String
"VK_FORMAT_R8G8B8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8_SRGB),
                  (String
"VK_FORMAT_B8G8R8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_UNORM),
                  (String
"VK_FORMAT_B8G8R8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_SNORM),
                  (String
"VK_FORMAT_B8G8R8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_USCALED),
                  (String
"VK_FORMAT_B8G8R8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_SSCALED),
                  (String
"VK_FORMAT_B8G8R8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_UINT),
                  (String
"VK_FORMAT_B8G8R8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_SINT),
                  (String
"VK_FORMAT_B8G8R8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8_SRGB),
                  (String
"VK_FORMAT_R8G8B8A8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_UNORM),
                  (String
"VK_FORMAT_R8G8B8A8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_SNORM),
                  (String
"VK_FORMAT_R8G8B8A8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_USCALED),
                  (String
"VK_FORMAT_R8G8B8A8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_SSCALED),
                  (String
"VK_FORMAT_R8G8B8A8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_UINT),
                  (String
"VK_FORMAT_R8G8B8A8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_SINT),
                  (String
"VK_FORMAT_R8G8B8A8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R8G8B8A8_SRGB),
                  (String
"VK_FORMAT_B8G8R8A8_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_UNORM),
                  (String
"VK_FORMAT_B8G8R8A8_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_SNORM),
                  (String
"VK_FORMAT_B8G8R8A8_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_USCALED),
                  (String
"VK_FORMAT_B8G8R8A8_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_SSCALED),
                  (String
"VK_FORMAT_B8G8R8A8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_UINT),
                  (String
"VK_FORMAT_B8G8R8A8_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_SINT),
                  (String
"VK_FORMAT_B8G8R8A8_SRGB", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B8G8R8A8_SRGB),
                  (String
"VK_FORMAT_A8B8G8R8_UNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_UNORM_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_SNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_SNORM_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_USCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_USCALED_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_SSCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_SSCALED_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_UINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_UINT_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_SINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_SINT_PACK32),
                  (String
"VK_FORMAT_A8B8G8R8_SRGB_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A8B8G8R8_SRGB_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_UNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_UNORM_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_SNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_SNORM_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_USCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_USCALED_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_SSCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_SSCALED_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_UINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_UINT_PACK32),
                  (String
"VK_FORMAT_A2R10G10B10_SINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2R10G10B10_SINT_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_UNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_UNORM_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_SNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_SNORM_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_USCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_USCALED_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_SSCALED_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_SSCALED_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_UINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_UINT_PACK32),
                  (String
"VK_FORMAT_A2B10G10R10_SINT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_A2B10G10R10_SINT_PACK32),
                  (String
"VK_FORMAT_R16_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_UNORM),
                  (String
"VK_FORMAT_R16_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_SNORM),
                  (String
"VK_FORMAT_R16_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_USCALED),
                  (String
"VK_FORMAT_R16_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_SSCALED),
                  (String
"VK_FORMAT_R16_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_UINT),
                  (String
"VK_FORMAT_R16_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_SINT),
                  (String
"VK_FORMAT_R16_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16_SFLOAT),
                  (String
"VK_FORMAT_R16G16_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_UNORM),
                  (String
"VK_FORMAT_R16G16_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_SNORM),
                  (String
"VK_FORMAT_R16G16_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_USCALED),
                  (String
"VK_FORMAT_R16G16_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_SSCALED),
                  (String
"VK_FORMAT_R16G16_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_UINT),
                  (String
"VK_FORMAT_R16G16_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_SINT),
                  (String
"VK_FORMAT_R16G16_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16_SFLOAT),
                  (String
"VK_FORMAT_R16G16B16_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_UNORM),
                  (String
"VK_FORMAT_R16G16B16_SNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_SNORM),
                  (String
"VK_FORMAT_R16G16B16_USCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_USCALED),
                  (String
"VK_FORMAT_R16G16B16_SSCALED", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_SSCALED),
                  (String
"VK_FORMAT_R16G16B16_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_UINT),
                  (String
"VK_FORMAT_R16G16B16_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_SINT),
                  (String
"VK_FORMAT_R16G16B16_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16_SFLOAT),
                  (String
"VK_FORMAT_R16G16B16A16_UNORM",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_UNORM),
                  (String
"VK_FORMAT_R16G16B16A16_SNORM",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_SNORM),
                  (String
"VK_FORMAT_R16G16B16A16_USCALED",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_USCALED),
                  (String
"VK_FORMAT_R16G16B16A16_SSCALED",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_SSCALED),
                  (String
"VK_FORMAT_R16G16B16A16_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_UINT),
                  (String
"VK_FORMAT_R16G16B16A16_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_SINT),
                  (String
"VK_FORMAT_R16G16B16A16_SFLOAT",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R16G16B16A16_SFLOAT),
                  (String
"VK_FORMAT_R32_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32_UINT),
                  (String
"VK_FORMAT_R32_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32_SINT),
                  (String
"VK_FORMAT_R32_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32_SFLOAT),
                  (String
"VK_FORMAT_R32G32_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32_UINT),
                  (String
"VK_FORMAT_R32G32_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32_SINT),
                  (String
"VK_FORMAT_R32G32_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32_SFLOAT),
                  (String
"VK_FORMAT_R32G32B32_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32_UINT),
                  (String
"VK_FORMAT_R32G32B32_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32_SINT),
                  (String
"VK_FORMAT_R32G32B32_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32_SFLOAT),
                  (String
"VK_FORMAT_R32G32B32A32_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32A32_UINT),
                  (String
"VK_FORMAT_R32G32B32A32_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32A32_SINT),
                  (String
"VK_FORMAT_R32G32B32A32_SFLOAT",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R32G32B32A32_SFLOAT),
                  (String
"VK_FORMAT_R64_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64_UINT),
                  (String
"VK_FORMAT_R64_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64_SINT),
                  (String
"VK_FORMAT_R64_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64_SFLOAT),
                  (String
"VK_FORMAT_R64G64_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64_UINT),
                  (String
"VK_FORMAT_R64G64_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64_SINT),
                  (String
"VK_FORMAT_R64G64_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64_SFLOAT),
                  (String
"VK_FORMAT_R64G64B64_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64_UINT),
                  (String
"VK_FORMAT_R64G64B64_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64_SINT),
                  (String
"VK_FORMAT_R64G64B64_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64_SFLOAT),
                  (String
"VK_FORMAT_R64G64B64A64_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64A64_UINT),
                  (String
"VK_FORMAT_R64G64B64A64_SINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64A64_SINT),
                  (String
"VK_FORMAT_R64G64B64A64_SFLOAT",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_R64G64B64A64_SFLOAT),
                  (String
"VK_FORMAT_B10G11R11_UFLOAT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_B10G11R11_UFLOAT_PACK32),
                  (String
"VK_FORMAT_E5B9G9R9_UFLOAT_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_E5B9G9R9_UFLOAT_PACK32),
                  (String
"VK_FORMAT_D16_UNORM", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_D16_UNORM),
                  (String
"VK_FORMAT_X8_D24_UNORM_PACK32",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_X8_D24_UNORM_PACK32),
                  (String
"VK_FORMAT_D32_SFLOAT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_D32_SFLOAT),
                  (String
"VK_FORMAT_S8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_S8_UINT),
                  (String
"VK_FORMAT_D16_UNORM_S8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_D16_UNORM_S8_UINT),
                  (String
"VK_FORMAT_D24_UNORM_S8_UINT", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_D24_UNORM_S8_UINT),
                  (String
"VK_FORMAT_D32_SFLOAT_S8_UINT",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_D32_SFLOAT_S8_UINT),
                  (String
"VK_FORMAT_BC1_RGB_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC1_RGB_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC1_RGB_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC1_RGB_SRGB_BLOCK),
                  (String
"VK_FORMAT_BC1_RGBA_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC1_RGBA_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC1_RGBA_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC1_RGBA_SRGB_BLOCK),
                  (String
"VK_FORMAT_BC2_UNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC2_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC2_SRGB_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC2_SRGB_BLOCK),
                  (String
"VK_FORMAT_BC3_UNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC3_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC3_SRGB_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC3_SRGB_BLOCK),
                  (String
"VK_FORMAT_BC4_UNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC4_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC4_SNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC4_SNORM_BLOCK),
                  (String
"VK_FORMAT_BC5_UNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC5_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC5_SNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC5_SNORM_BLOCK),
                  (String
"VK_FORMAT_BC6H_UFLOAT_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC6H_UFLOAT_BLOCK),
                  (String
"VK_FORMAT_BC6H_SFLOAT_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC6H_SFLOAT_BLOCK),
                  (String
"VK_FORMAT_BC7_UNORM_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC7_UNORM_BLOCK),
                  (String
"VK_FORMAT_BC7_SRGB_BLOCK", VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_BC7_SRGB_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK),
                  (String
"VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK),
                  (String
"VK_FORMAT_EAC_R11_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_EAC_R11_UNORM_BLOCK),
                  (String
"VK_FORMAT_EAC_R11_SNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_EAC_R11_SNORM_BLOCK),
                  (String
"VK_FORMAT_EAC_R11G11_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_EAC_R11G11_UNORM_BLOCK),
                  (String
"VK_FORMAT_EAC_R11G11_SNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_EAC_R11G11_SNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_4x4_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_4x4_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_4x4_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_4x4_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_5x4_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_5x4_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_5x4_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_5x4_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_5x5_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_5x5_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_5x5_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_5x5_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_6x5_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_6x5_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_6x5_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_6x5_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_6x6_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_6x6_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_6x6_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_6x6_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x5_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x5_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x5_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x5_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x6_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x6_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x6_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x6_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x8_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x8_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_8x8_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_8x8_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x5_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x5_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x5_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x5_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x6_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x6_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x6_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x6_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x8_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x8_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x8_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x8_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x10_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x10_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_10x10_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_10x10_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_12x10_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_12x10_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_12x10_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_12x10_SRGB_BLOCK),
                  (String
"VK_FORMAT_ASTC_12x12_UNORM_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_12x12_UNORM_BLOCK),
                  (String
"VK_FORMAT_ASTC_12x12_SRGB_BLOCK",
                   VkFormat -> ReadPrec VkFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormat
VK_FORMAT_ASTC_12x12_SRGB_BLOCK)]
                 ReadPrec VkFormat -> ReadPrec VkFormat -> ReadPrec VkFormat
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int -> ReadPrec VkFormat -> ReadPrec VkFormat
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkFormat") ReadPrec () -> ReadPrec VkFormat -> ReadPrec VkFormat
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Int32 -> VkFormat
VkFormat (Int32 -> VkFormat) -> ReadPrec Int32 -> ReadPrec VkFormat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_FORMAT_UNDEFINED :: VkFormat

pattern $bVK_FORMAT_UNDEFINED :: VkFormat
$mVK_FORMAT_UNDEFINED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_UNDEFINED = VkFormat 0

pattern VK_FORMAT_R4G4_UNORM_PACK8 :: VkFormat

pattern $bVK_FORMAT_R4G4_UNORM_PACK8 :: VkFormat
$mVK_FORMAT_R4G4_UNORM_PACK8 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R4G4_UNORM_PACK8 = VkFormat 1

pattern VK_FORMAT_R4G4B4A4_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_R4G4B4A4_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_R4G4B4A4_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R4G4B4A4_UNORM_PACK16 = VkFormat 2

pattern VK_FORMAT_B4G4R4A4_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_B4G4R4A4_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_B4G4R4A4_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B4G4R4A4_UNORM_PACK16 = VkFormat 3

pattern VK_FORMAT_R5G6B5_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_R5G6B5_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_R5G6B5_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R5G6B5_UNORM_PACK16 = VkFormat 4

pattern VK_FORMAT_B5G6R5_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_B5G6R5_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_B5G6R5_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B5G6R5_UNORM_PACK16 = VkFormat 5

pattern VK_FORMAT_R5G5B5A1_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_R5G5B5A1_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_R5G5B5A1_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R5G5B5A1_UNORM_PACK16 = VkFormat 6

pattern VK_FORMAT_B5G5R5A1_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_B5G5R5A1_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_B5G5R5A1_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B5G5R5A1_UNORM_PACK16 = VkFormat 7

pattern VK_FORMAT_A1R5G5B5_UNORM_PACK16 :: VkFormat

pattern $bVK_FORMAT_A1R5G5B5_UNORM_PACK16 :: VkFormat
$mVK_FORMAT_A1R5G5B5_UNORM_PACK16 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A1R5G5B5_UNORM_PACK16 = VkFormat 8

pattern VK_FORMAT_R8_UNORM :: VkFormat

pattern $bVK_FORMAT_R8_UNORM :: VkFormat
$mVK_FORMAT_R8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_UNORM = VkFormat 9

pattern VK_FORMAT_R8_SNORM :: VkFormat

pattern $bVK_FORMAT_R8_SNORM :: VkFormat
$mVK_FORMAT_R8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_SNORM = VkFormat 10

pattern VK_FORMAT_R8_USCALED :: VkFormat

pattern $bVK_FORMAT_R8_USCALED :: VkFormat
$mVK_FORMAT_R8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_USCALED = VkFormat 11

pattern VK_FORMAT_R8_SSCALED :: VkFormat

pattern $bVK_FORMAT_R8_SSCALED :: VkFormat
$mVK_FORMAT_R8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_SSCALED = VkFormat 12

pattern VK_FORMAT_R8_UINT :: VkFormat

pattern $bVK_FORMAT_R8_UINT :: VkFormat
$mVK_FORMAT_R8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_UINT = VkFormat 13

pattern VK_FORMAT_R8_SINT :: VkFormat

pattern $bVK_FORMAT_R8_SINT :: VkFormat
$mVK_FORMAT_R8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_SINT = VkFormat 14

pattern VK_FORMAT_R8_SRGB :: VkFormat

pattern $bVK_FORMAT_R8_SRGB :: VkFormat
$mVK_FORMAT_R8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8_SRGB = VkFormat 15

pattern VK_FORMAT_R8G8_UNORM :: VkFormat

pattern $bVK_FORMAT_R8G8_UNORM :: VkFormat
$mVK_FORMAT_R8G8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_UNORM = VkFormat 16

pattern VK_FORMAT_R8G8_SNORM :: VkFormat

pattern $bVK_FORMAT_R8G8_SNORM :: VkFormat
$mVK_FORMAT_R8G8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_SNORM = VkFormat 17

pattern VK_FORMAT_R8G8_USCALED :: VkFormat

pattern $bVK_FORMAT_R8G8_USCALED :: VkFormat
$mVK_FORMAT_R8G8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_USCALED = VkFormat 18

pattern VK_FORMAT_R8G8_SSCALED :: VkFormat

pattern $bVK_FORMAT_R8G8_SSCALED :: VkFormat
$mVK_FORMAT_R8G8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_SSCALED = VkFormat 19

pattern VK_FORMAT_R8G8_UINT :: VkFormat

pattern $bVK_FORMAT_R8G8_UINT :: VkFormat
$mVK_FORMAT_R8G8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_UINT = VkFormat 20

pattern VK_FORMAT_R8G8_SINT :: VkFormat

pattern $bVK_FORMAT_R8G8_SINT :: VkFormat
$mVK_FORMAT_R8G8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_SINT = VkFormat 21

pattern VK_FORMAT_R8G8_SRGB :: VkFormat

pattern $bVK_FORMAT_R8G8_SRGB :: VkFormat
$mVK_FORMAT_R8G8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8_SRGB = VkFormat 22

pattern VK_FORMAT_R8G8B8_UNORM :: VkFormat

pattern $bVK_FORMAT_R8G8B8_UNORM :: VkFormat
$mVK_FORMAT_R8G8B8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_UNORM = VkFormat 23

pattern VK_FORMAT_R8G8B8_SNORM :: VkFormat

pattern $bVK_FORMAT_R8G8B8_SNORM :: VkFormat
$mVK_FORMAT_R8G8B8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_SNORM = VkFormat 24

pattern VK_FORMAT_R8G8B8_USCALED :: VkFormat

pattern $bVK_FORMAT_R8G8B8_USCALED :: VkFormat
$mVK_FORMAT_R8G8B8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_USCALED = VkFormat 25

pattern VK_FORMAT_R8G8B8_SSCALED :: VkFormat

pattern $bVK_FORMAT_R8G8B8_SSCALED :: VkFormat
$mVK_FORMAT_R8G8B8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_SSCALED = VkFormat 26

pattern VK_FORMAT_R8G8B8_UINT :: VkFormat

pattern $bVK_FORMAT_R8G8B8_UINT :: VkFormat
$mVK_FORMAT_R8G8B8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_UINT = VkFormat 27

pattern VK_FORMAT_R8G8B8_SINT :: VkFormat

pattern $bVK_FORMAT_R8G8B8_SINT :: VkFormat
$mVK_FORMAT_R8G8B8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_SINT = VkFormat 28

pattern VK_FORMAT_R8G8B8_SRGB :: VkFormat

pattern $bVK_FORMAT_R8G8B8_SRGB :: VkFormat
$mVK_FORMAT_R8G8B8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8_SRGB = VkFormat 29

pattern VK_FORMAT_B8G8R8_UNORM :: VkFormat

pattern $bVK_FORMAT_B8G8R8_UNORM :: VkFormat
$mVK_FORMAT_B8G8R8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_UNORM = VkFormat 30

pattern VK_FORMAT_B8G8R8_SNORM :: VkFormat

pattern $bVK_FORMAT_B8G8R8_SNORM :: VkFormat
$mVK_FORMAT_B8G8R8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_SNORM = VkFormat 31

pattern VK_FORMAT_B8G8R8_USCALED :: VkFormat

pattern $bVK_FORMAT_B8G8R8_USCALED :: VkFormat
$mVK_FORMAT_B8G8R8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_USCALED = VkFormat 32

pattern VK_FORMAT_B8G8R8_SSCALED :: VkFormat

pattern $bVK_FORMAT_B8G8R8_SSCALED :: VkFormat
$mVK_FORMAT_B8G8R8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_SSCALED = VkFormat 33

pattern VK_FORMAT_B8G8R8_UINT :: VkFormat

pattern $bVK_FORMAT_B8G8R8_UINT :: VkFormat
$mVK_FORMAT_B8G8R8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_UINT = VkFormat 34

pattern VK_FORMAT_B8G8R8_SINT :: VkFormat

pattern $bVK_FORMAT_B8G8R8_SINT :: VkFormat
$mVK_FORMAT_B8G8R8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_SINT = VkFormat 35

pattern VK_FORMAT_B8G8R8_SRGB :: VkFormat

pattern $bVK_FORMAT_B8G8R8_SRGB :: VkFormat
$mVK_FORMAT_B8G8R8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8_SRGB = VkFormat 36

pattern VK_FORMAT_R8G8B8A8_UNORM :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_UNORM :: VkFormat
$mVK_FORMAT_R8G8B8A8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_UNORM = VkFormat 37

pattern VK_FORMAT_R8G8B8A8_SNORM :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_SNORM :: VkFormat
$mVK_FORMAT_R8G8B8A8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_SNORM = VkFormat 38

pattern VK_FORMAT_R8G8B8A8_USCALED :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_USCALED :: VkFormat
$mVK_FORMAT_R8G8B8A8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_USCALED = VkFormat 39

pattern VK_FORMAT_R8G8B8A8_SSCALED :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_SSCALED :: VkFormat
$mVK_FORMAT_R8G8B8A8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_SSCALED = VkFormat 40

pattern VK_FORMAT_R8G8B8A8_UINT :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_UINT :: VkFormat
$mVK_FORMAT_R8G8B8A8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_UINT = VkFormat 41

pattern VK_FORMAT_R8G8B8A8_SINT :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_SINT :: VkFormat
$mVK_FORMAT_R8G8B8A8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_SINT = VkFormat 42

pattern VK_FORMAT_R8G8B8A8_SRGB :: VkFormat

pattern $bVK_FORMAT_R8G8B8A8_SRGB :: VkFormat
$mVK_FORMAT_R8G8B8A8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R8G8B8A8_SRGB = VkFormat 43

pattern VK_FORMAT_B8G8R8A8_UNORM :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_UNORM :: VkFormat
$mVK_FORMAT_B8G8R8A8_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_UNORM = VkFormat 44

pattern VK_FORMAT_B8G8R8A8_SNORM :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_SNORM :: VkFormat
$mVK_FORMAT_B8G8R8A8_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_SNORM = VkFormat 45

pattern VK_FORMAT_B8G8R8A8_USCALED :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_USCALED :: VkFormat
$mVK_FORMAT_B8G8R8A8_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_USCALED = VkFormat 46

pattern VK_FORMAT_B8G8R8A8_SSCALED :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_SSCALED :: VkFormat
$mVK_FORMAT_B8G8R8A8_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_SSCALED = VkFormat 47

pattern VK_FORMAT_B8G8R8A8_UINT :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_UINT :: VkFormat
$mVK_FORMAT_B8G8R8A8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_UINT = VkFormat 48

pattern VK_FORMAT_B8G8R8A8_SINT :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_SINT :: VkFormat
$mVK_FORMAT_B8G8R8A8_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_SINT = VkFormat 49

pattern VK_FORMAT_B8G8R8A8_SRGB :: VkFormat

pattern $bVK_FORMAT_B8G8R8A8_SRGB :: VkFormat
$mVK_FORMAT_B8G8R8A8_SRGB :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B8G8R8A8_SRGB = VkFormat 50

pattern VK_FORMAT_A8B8G8R8_UNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_UNORM_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_UNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_UNORM_PACK32 = VkFormat 51

pattern VK_FORMAT_A8B8G8R8_SNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_SNORM_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_SNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_SNORM_PACK32 = VkFormat 52

pattern VK_FORMAT_A8B8G8R8_USCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_USCALED_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_USCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_USCALED_PACK32 = VkFormat 53

pattern VK_FORMAT_A8B8G8R8_SSCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_SSCALED_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_SSCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_SSCALED_PACK32 = VkFormat 54

pattern VK_FORMAT_A8B8G8R8_UINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_UINT_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_UINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_UINT_PACK32 = VkFormat 55

pattern VK_FORMAT_A8B8G8R8_SINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_SINT_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_SINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_SINT_PACK32 = VkFormat 56

pattern VK_FORMAT_A8B8G8R8_SRGB_PACK32 :: VkFormat

pattern $bVK_FORMAT_A8B8G8R8_SRGB_PACK32 :: VkFormat
$mVK_FORMAT_A8B8G8R8_SRGB_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A8B8G8R8_SRGB_PACK32 = VkFormat 57

pattern VK_FORMAT_A2R10G10B10_UNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_UNORM_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_UNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_UNORM_PACK32 = VkFormat 58

pattern VK_FORMAT_A2R10G10B10_SNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_SNORM_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_SNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_SNORM_PACK32 = VkFormat 59

pattern VK_FORMAT_A2R10G10B10_USCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_USCALED_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_USCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_USCALED_PACK32 = VkFormat 60

pattern VK_FORMAT_A2R10G10B10_SSCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_SSCALED_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_SSCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_SSCALED_PACK32 = VkFormat 61

pattern VK_FORMAT_A2R10G10B10_UINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_UINT_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_UINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_UINT_PACK32 = VkFormat 62

pattern VK_FORMAT_A2R10G10B10_SINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2R10G10B10_SINT_PACK32 :: VkFormat
$mVK_FORMAT_A2R10G10B10_SINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2R10G10B10_SINT_PACK32 = VkFormat 63

pattern VK_FORMAT_A2B10G10R10_UNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_UNORM_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_UNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_UNORM_PACK32 = VkFormat 64

pattern VK_FORMAT_A2B10G10R10_SNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_SNORM_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_SNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_SNORM_PACK32 = VkFormat 65

pattern VK_FORMAT_A2B10G10R10_USCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_USCALED_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_USCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_USCALED_PACK32 = VkFormat 66

pattern VK_FORMAT_A2B10G10R10_SSCALED_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_SSCALED_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_SSCALED_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_SSCALED_PACK32 = VkFormat 67

pattern VK_FORMAT_A2B10G10R10_UINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_UINT_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_UINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_UINT_PACK32 = VkFormat 68

pattern VK_FORMAT_A2B10G10R10_SINT_PACK32 :: VkFormat

pattern $bVK_FORMAT_A2B10G10R10_SINT_PACK32 :: VkFormat
$mVK_FORMAT_A2B10G10R10_SINT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_A2B10G10R10_SINT_PACK32 = VkFormat 69

pattern VK_FORMAT_R16_UNORM :: VkFormat

pattern $bVK_FORMAT_R16_UNORM :: VkFormat
$mVK_FORMAT_R16_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_UNORM = VkFormat 70

pattern VK_FORMAT_R16_SNORM :: VkFormat

pattern $bVK_FORMAT_R16_SNORM :: VkFormat
$mVK_FORMAT_R16_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_SNORM = VkFormat 71

pattern VK_FORMAT_R16_USCALED :: VkFormat

pattern $bVK_FORMAT_R16_USCALED :: VkFormat
$mVK_FORMAT_R16_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_USCALED = VkFormat 72

pattern VK_FORMAT_R16_SSCALED :: VkFormat

pattern $bVK_FORMAT_R16_SSCALED :: VkFormat
$mVK_FORMAT_R16_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_SSCALED = VkFormat 73

pattern VK_FORMAT_R16_UINT :: VkFormat

pattern $bVK_FORMAT_R16_UINT :: VkFormat
$mVK_FORMAT_R16_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_UINT = VkFormat 74

pattern VK_FORMAT_R16_SINT :: VkFormat

pattern $bVK_FORMAT_R16_SINT :: VkFormat
$mVK_FORMAT_R16_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_SINT = VkFormat 75

pattern VK_FORMAT_R16_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R16_SFLOAT :: VkFormat
$mVK_FORMAT_R16_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16_SFLOAT = VkFormat 76

pattern VK_FORMAT_R16G16_UNORM :: VkFormat

pattern $bVK_FORMAT_R16G16_UNORM :: VkFormat
$mVK_FORMAT_R16G16_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_UNORM = VkFormat 77

pattern VK_FORMAT_R16G16_SNORM :: VkFormat

pattern $bVK_FORMAT_R16G16_SNORM :: VkFormat
$mVK_FORMAT_R16G16_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_SNORM = VkFormat 78

pattern VK_FORMAT_R16G16_USCALED :: VkFormat

pattern $bVK_FORMAT_R16G16_USCALED :: VkFormat
$mVK_FORMAT_R16G16_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_USCALED = VkFormat 79

pattern VK_FORMAT_R16G16_SSCALED :: VkFormat

pattern $bVK_FORMAT_R16G16_SSCALED :: VkFormat
$mVK_FORMAT_R16G16_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_SSCALED = VkFormat 80

pattern VK_FORMAT_R16G16_UINT :: VkFormat

pattern $bVK_FORMAT_R16G16_UINT :: VkFormat
$mVK_FORMAT_R16G16_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_UINT = VkFormat 81

pattern VK_FORMAT_R16G16_SINT :: VkFormat

pattern $bVK_FORMAT_R16G16_SINT :: VkFormat
$mVK_FORMAT_R16G16_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_SINT = VkFormat 82

pattern VK_FORMAT_R16G16_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R16G16_SFLOAT :: VkFormat
$mVK_FORMAT_R16G16_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16_SFLOAT = VkFormat 83

pattern VK_FORMAT_R16G16B16_UNORM :: VkFormat

pattern $bVK_FORMAT_R16G16B16_UNORM :: VkFormat
$mVK_FORMAT_R16G16B16_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_UNORM = VkFormat 84

pattern VK_FORMAT_R16G16B16_SNORM :: VkFormat

pattern $bVK_FORMAT_R16G16B16_SNORM :: VkFormat
$mVK_FORMAT_R16G16B16_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_SNORM = VkFormat 85

pattern VK_FORMAT_R16G16B16_USCALED :: VkFormat

pattern $bVK_FORMAT_R16G16B16_USCALED :: VkFormat
$mVK_FORMAT_R16G16B16_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_USCALED = VkFormat 86

pattern VK_FORMAT_R16G16B16_SSCALED :: VkFormat

pattern $bVK_FORMAT_R16G16B16_SSCALED :: VkFormat
$mVK_FORMAT_R16G16B16_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_SSCALED = VkFormat 87

pattern VK_FORMAT_R16G16B16_UINT :: VkFormat

pattern $bVK_FORMAT_R16G16B16_UINT :: VkFormat
$mVK_FORMAT_R16G16B16_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_UINT = VkFormat 88

pattern VK_FORMAT_R16G16B16_SINT :: VkFormat

pattern $bVK_FORMAT_R16G16B16_SINT :: VkFormat
$mVK_FORMAT_R16G16B16_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_SINT = VkFormat 89

pattern VK_FORMAT_R16G16B16_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R16G16B16_SFLOAT :: VkFormat
$mVK_FORMAT_R16G16B16_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16_SFLOAT = VkFormat 90

pattern VK_FORMAT_R16G16B16A16_UNORM :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_UNORM :: VkFormat
$mVK_FORMAT_R16G16B16A16_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_UNORM = VkFormat 91

pattern VK_FORMAT_R16G16B16A16_SNORM :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_SNORM :: VkFormat
$mVK_FORMAT_R16G16B16A16_SNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_SNORM = VkFormat 92

pattern VK_FORMAT_R16G16B16A16_USCALED :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_USCALED :: VkFormat
$mVK_FORMAT_R16G16B16A16_USCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_USCALED = VkFormat 93

pattern VK_FORMAT_R16G16B16A16_SSCALED :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_SSCALED :: VkFormat
$mVK_FORMAT_R16G16B16A16_SSCALED :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_SSCALED = VkFormat 94

pattern VK_FORMAT_R16G16B16A16_UINT :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_UINT :: VkFormat
$mVK_FORMAT_R16G16B16A16_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_UINT = VkFormat 95

pattern VK_FORMAT_R16G16B16A16_SINT :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_SINT :: VkFormat
$mVK_FORMAT_R16G16B16A16_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_SINT = VkFormat 96

pattern VK_FORMAT_R16G16B16A16_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R16G16B16A16_SFLOAT :: VkFormat
$mVK_FORMAT_R16G16B16A16_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R16G16B16A16_SFLOAT = VkFormat 97

pattern VK_FORMAT_R32_UINT :: VkFormat

pattern $bVK_FORMAT_R32_UINT :: VkFormat
$mVK_FORMAT_R32_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32_UINT = VkFormat 98

pattern VK_FORMAT_R32_SINT :: VkFormat

pattern $bVK_FORMAT_R32_SINT :: VkFormat
$mVK_FORMAT_R32_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32_SINT = VkFormat 99

pattern VK_FORMAT_R32_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R32_SFLOAT :: VkFormat
$mVK_FORMAT_R32_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32_SFLOAT = VkFormat 100

pattern VK_FORMAT_R32G32_UINT :: VkFormat

pattern $bVK_FORMAT_R32G32_UINT :: VkFormat
$mVK_FORMAT_R32G32_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32_UINT = VkFormat 101

pattern VK_FORMAT_R32G32_SINT :: VkFormat

pattern $bVK_FORMAT_R32G32_SINT :: VkFormat
$mVK_FORMAT_R32G32_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32_SINT = VkFormat 102

pattern VK_FORMAT_R32G32_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R32G32_SFLOAT :: VkFormat
$mVK_FORMAT_R32G32_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32_SFLOAT = VkFormat 103

pattern VK_FORMAT_R32G32B32_UINT :: VkFormat

pattern $bVK_FORMAT_R32G32B32_UINT :: VkFormat
$mVK_FORMAT_R32G32B32_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32_UINT = VkFormat 104

pattern VK_FORMAT_R32G32B32_SINT :: VkFormat

pattern $bVK_FORMAT_R32G32B32_SINT :: VkFormat
$mVK_FORMAT_R32G32B32_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32_SINT = VkFormat 105

pattern VK_FORMAT_R32G32B32_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R32G32B32_SFLOAT :: VkFormat
$mVK_FORMAT_R32G32B32_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32_SFLOAT = VkFormat 106

pattern VK_FORMAT_R32G32B32A32_UINT :: VkFormat

pattern $bVK_FORMAT_R32G32B32A32_UINT :: VkFormat
$mVK_FORMAT_R32G32B32A32_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32A32_UINT = VkFormat 107

pattern VK_FORMAT_R32G32B32A32_SINT :: VkFormat

pattern $bVK_FORMAT_R32G32B32A32_SINT :: VkFormat
$mVK_FORMAT_R32G32B32A32_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32A32_SINT = VkFormat 108

pattern VK_FORMAT_R32G32B32A32_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R32G32B32A32_SFLOAT :: VkFormat
$mVK_FORMAT_R32G32B32A32_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R32G32B32A32_SFLOAT = VkFormat 109

pattern VK_FORMAT_R64_UINT :: VkFormat

pattern $bVK_FORMAT_R64_UINT :: VkFormat
$mVK_FORMAT_R64_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64_UINT = VkFormat 110

pattern VK_FORMAT_R64_SINT :: VkFormat

pattern $bVK_FORMAT_R64_SINT :: VkFormat
$mVK_FORMAT_R64_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64_SINT = VkFormat 111

pattern VK_FORMAT_R64_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R64_SFLOAT :: VkFormat
$mVK_FORMAT_R64_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64_SFLOAT = VkFormat 112

pattern VK_FORMAT_R64G64_UINT :: VkFormat

pattern $bVK_FORMAT_R64G64_UINT :: VkFormat
$mVK_FORMAT_R64G64_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64_UINT = VkFormat 113

pattern VK_FORMAT_R64G64_SINT :: VkFormat

pattern $bVK_FORMAT_R64G64_SINT :: VkFormat
$mVK_FORMAT_R64G64_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64_SINT = VkFormat 114

pattern VK_FORMAT_R64G64_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R64G64_SFLOAT :: VkFormat
$mVK_FORMAT_R64G64_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64_SFLOAT = VkFormat 115

pattern VK_FORMAT_R64G64B64_UINT :: VkFormat

pattern $bVK_FORMAT_R64G64B64_UINT :: VkFormat
$mVK_FORMAT_R64G64B64_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64_UINT = VkFormat 116

pattern VK_FORMAT_R64G64B64_SINT :: VkFormat

pattern $bVK_FORMAT_R64G64B64_SINT :: VkFormat
$mVK_FORMAT_R64G64B64_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64_SINT = VkFormat 117

pattern VK_FORMAT_R64G64B64_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R64G64B64_SFLOAT :: VkFormat
$mVK_FORMAT_R64G64B64_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64_SFLOAT = VkFormat 118

pattern VK_FORMAT_R64G64B64A64_UINT :: VkFormat

pattern $bVK_FORMAT_R64G64B64A64_UINT :: VkFormat
$mVK_FORMAT_R64G64B64A64_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64A64_UINT = VkFormat 119

pattern VK_FORMAT_R64G64B64A64_SINT :: VkFormat

pattern $bVK_FORMAT_R64G64B64A64_SINT :: VkFormat
$mVK_FORMAT_R64G64B64A64_SINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64A64_SINT = VkFormat 120

pattern VK_FORMAT_R64G64B64A64_SFLOAT :: VkFormat

pattern $bVK_FORMAT_R64G64B64A64_SFLOAT :: VkFormat
$mVK_FORMAT_R64G64B64A64_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_R64G64B64A64_SFLOAT = VkFormat 121

pattern VK_FORMAT_B10G11R11_UFLOAT_PACK32 :: VkFormat

pattern $bVK_FORMAT_B10G11R11_UFLOAT_PACK32 :: VkFormat
$mVK_FORMAT_B10G11R11_UFLOAT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_B10G11R11_UFLOAT_PACK32 = VkFormat 122

pattern VK_FORMAT_E5B9G9R9_UFLOAT_PACK32 :: VkFormat

pattern $bVK_FORMAT_E5B9G9R9_UFLOAT_PACK32 :: VkFormat
$mVK_FORMAT_E5B9G9R9_UFLOAT_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_E5B9G9R9_UFLOAT_PACK32 = VkFormat 123

pattern VK_FORMAT_D16_UNORM :: VkFormat

pattern $bVK_FORMAT_D16_UNORM :: VkFormat
$mVK_FORMAT_D16_UNORM :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_D16_UNORM = VkFormat 124

pattern VK_FORMAT_X8_D24_UNORM_PACK32 :: VkFormat

pattern $bVK_FORMAT_X8_D24_UNORM_PACK32 :: VkFormat
$mVK_FORMAT_X8_D24_UNORM_PACK32 :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_X8_D24_UNORM_PACK32 = VkFormat 125

pattern VK_FORMAT_D32_SFLOAT :: VkFormat

pattern $bVK_FORMAT_D32_SFLOAT :: VkFormat
$mVK_FORMAT_D32_SFLOAT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_D32_SFLOAT = VkFormat 126

pattern VK_FORMAT_S8_UINT :: VkFormat

pattern $bVK_FORMAT_S8_UINT :: VkFormat
$mVK_FORMAT_S8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_S8_UINT = VkFormat 127

pattern VK_FORMAT_D16_UNORM_S8_UINT :: VkFormat

pattern $bVK_FORMAT_D16_UNORM_S8_UINT :: VkFormat
$mVK_FORMAT_D16_UNORM_S8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_D16_UNORM_S8_UINT = VkFormat 128

pattern VK_FORMAT_D24_UNORM_S8_UINT :: VkFormat

pattern $bVK_FORMAT_D24_UNORM_S8_UINT :: VkFormat
$mVK_FORMAT_D24_UNORM_S8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_D24_UNORM_S8_UINT = VkFormat 129

pattern VK_FORMAT_D32_SFLOAT_S8_UINT :: VkFormat

pattern $bVK_FORMAT_D32_SFLOAT_S8_UINT :: VkFormat
$mVK_FORMAT_D32_SFLOAT_S8_UINT :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_D32_SFLOAT_S8_UINT = VkFormat 130

pattern VK_FORMAT_BC1_RGB_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC1_RGB_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC1_RGB_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC1_RGB_UNORM_BLOCK = VkFormat 131

pattern VK_FORMAT_BC1_RGB_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC1_RGB_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_BC1_RGB_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC1_RGB_SRGB_BLOCK = VkFormat 132

pattern VK_FORMAT_BC1_RGBA_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC1_RGBA_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC1_RGBA_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC1_RGBA_UNORM_BLOCK = VkFormat 133

pattern VK_FORMAT_BC1_RGBA_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC1_RGBA_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_BC1_RGBA_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC1_RGBA_SRGB_BLOCK = VkFormat 134

pattern VK_FORMAT_BC2_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC2_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC2_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC2_UNORM_BLOCK = VkFormat 135

pattern VK_FORMAT_BC2_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC2_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_BC2_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC2_SRGB_BLOCK = VkFormat 136

pattern VK_FORMAT_BC3_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC3_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC3_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC3_UNORM_BLOCK = VkFormat 137

pattern VK_FORMAT_BC3_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC3_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_BC3_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC3_SRGB_BLOCK = VkFormat 138

pattern VK_FORMAT_BC4_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC4_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC4_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC4_UNORM_BLOCK = VkFormat 139

pattern VK_FORMAT_BC4_SNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC4_SNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC4_SNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC4_SNORM_BLOCK = VkFormat 140

pattern VK_FORMAT_BC5_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC5_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC5_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC5_UNORM_BLOCK = VkFormat 141

pattern VK_FORMAT_BC5_SNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC5_SNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC5_SNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC5_SNORM_BLOCK = VkFormat 142

pattern VK_FORMAT_BC6H_UFLOAT_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC6H_UFLOAT_BLOCK :: VkFormat
$mVK_FORMAT_BC6H_UFLOAT_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC6H_UFLOAT_BLOCK = VkFormat 143

pattern VK_FORMAT_BC6H_SFLOAT_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC6H_SFLOAT_BLOCK :: VkFormat
$mVK_FORMAT_BC6H_SFLOAT_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC6H_SFLOAT_BLOCK = VkFormat 144

pattern VK_FORMAT_BC7_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC7_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_BC7_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC7_UNORM_BLOCK = VkFormat 145

pattern VK_FORMAT_BC7_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_BC7_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_BC7_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_BC7_SRGB_BLOCK = VkFormat 146

pattern VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8_UNORM_BLOCK = VkFormat 147

pattern VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8_SRGB_BLOCK = VkFormat 148

pattern VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK = VkFormat 149

pattern VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK = VkFormat 150

pattern VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK = VkFormat 151

pattern VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK = VkFormat 152

pattern VK_FORMAT_EAC_R11_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_EAC_R11_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_EAC_R11_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_EAC_R11_UNORM_BLOCK = VkFormat 153

pattern VK_FORMAT_EAC_R11_SNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_EAC_R11_SNORM_BLOCK :: VkFormat
$mVK_FORMAT_EAC_R11_SNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_EAC_R11_SNORM_BLOCK = VkFormat 154

pattern VK_FORMAT_EAC_R11G11_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_EAC_R11G11_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_EAC_R11G11_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_EAC_R11G11_UNORM_BLOCK = VkFormat 155

pattern VK_FORMAT_EAC_R11G11_SNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_EAC_R11G11_SNORM_BLOCK :: VkFormat
$mVK_FORMAT_EAC_R11G11_SNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_EAC_R11G11_SNORM_BLOCK = VkFormat 156

pattern VK_FORMAT_ASTC_4x4_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_4x4_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_4x4_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_4x4_UNORM_BLOCK = VkFormat 157

pattern VK_FORMAT_ASTC_4x4_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_4x4_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_4x4_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_4x4_SRGB_BLOCK = VkFormat 158

pattern VK_FORMAT_ASTC_5x4_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_5x4_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_5x4_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_5x4_UNORM_BLOCK = VkFormat 159

pattern VK_FORMAT_ASTC_5x4_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_5x4_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_5x4_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_5x4_SRGB_BLOCK = VkFormat 160

pattern VK_FORMAT_ASTC_5x5_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_5x5_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_5x5_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_5x5_UNORM_BLOCK = VkFormat 161

pattern VK_FORMAT_ASTC_5x5_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_5x5_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_5x5_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_5x5_SRGB_BLOCK = VkFormat 162

pattern VK_FORMAT_ASTC_6x5_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_6x5_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_6x5_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_6x5_UNORM_BLOCK = VkFormat 163

pattern VK_FORMAT_ASTC_6x5_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_6x5_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_6x5_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_6x5_SRGB_BLOCK = VkFormat 164

pattern VK_FORMAT_ASTC_6x6_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_6x6_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_6x6_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_6x6_UNORM_BLOCK = VkFormat 165

pattern VK_FORMAT_ASTC_6x6_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_6x6_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_6x6_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_6x6_SRGB_BLOCK = VkFormat 166

pattern VK_FORMAT_ASTC_8x5_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x5_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x5_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x5_UNORM_BLOCK = VkFormat 167

pattern VK_FORMAT_ASTC_8x5_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x5_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x5_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x5_SRGB_BLOCK = VkFormat 168

pattern VK_FORMAT_ASTC_8x6_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x6_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x6_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x6_UNORM_BLOCK = VkFormat 169

pattern VK_FORMAT_ASTC_8x6_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x6_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x6_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x6_SRGB_BLOCK = VkFormat 170

pattern VK_FORMAT_ASTC_8x8_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x8_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x8_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x8_UNORM_BLOCK = VkFormat 171

pattern VK_FORMAT_ASTC_8x8_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_8x8_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_8x8_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_8x8_SRGB_BLOCK = VkFormat 172

pattern VK_FORMAT_ASTC_10x5_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x5_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x5_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x5_UNORM_BLOCK = VkFormat 173

pattern VK_FORMAT_ASTC_10x5_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x5_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x5_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x5_SRGB_BLOCK = VkFormat 174

pattern VK_FORMAT_ASTC_10x6_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x6_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x6_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x6_UNORM_BLOCK = VkFormat 175

pattern VK_FORMAT_ASTC_10x6_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x6_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x6_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x6_SRGB_BLOCK = VkFormat 176

pattern VK_FORMAT_ASTC_10x8_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x8_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x8_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x8_UNORM_BLOCK = VkFormat 177

pattern VK_FORMAT_ASTC_10x8_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x8_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x8_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x8_SRGB_BLOCK = VkFormat 178

pattern VK_FORMAT_ASTC_10x10_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x10_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x10_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x10_UNORM_BLOCK = VkFormat 179

pattern VK_FORMAT_ASTC_10x10_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_10x10_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_10x10_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_10x10_SRGB_BLOCK = VkFormat 180

pattern VK_FORMAT_ASTC_12x10_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_12x10_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_12x10_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_12x10_UNORM_BLOCK = VkFormat 181

pattern VK_FORMAT_ASTC_12x10_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_12x10_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_12x10_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_12x10_SRGB_BLOCK = VkFormat 182

pattern VK_FORMAT_ASTC_12x12_UNORM_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_12x12_UNORM_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_12x12_UNORM_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_12x12_UNORM_BLOCK = VkFormat 183

pattern VK_FORMAT_ASTC_12x12_SRGB_BLOCK :: VkFormat

pattern $bVK_FORMAT_ASTC_12x12_SRGB_BLOCK :: VkFormat
$mVK_FORMAT_ASTC_12x12_SRGB_BLOCK :: forall r. VkFormat -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_ASTC_12x12_SRGB_BLOCK = VkFormat 184

newtype VkFormatFeatureBitmask (a ::
                                  FlagType) = VkFormatFeatureBitmask VkFlags
                                                deriving (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
(VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> Eq (VkFormatFeatureBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
/= :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
== :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
Eq, Eq (VkFormatFeatureBitmask a)
Eq (VkFormatFeatureBitmask a)
-> (VkFormatFeatureBitmask a
    -> VkFormatFeatureBitmask a -> Ordering)
-> (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> (VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool)
-> (VkFormatFeatureBitmask a
    -> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a)
-> (VkFormatFeatureBitmask a
    -> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a)
-> Ord (VkFormatFeatureBitmask a)
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Ordering
VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
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
forall (a :: FlagType). Eq (VkFormatFeatureBitmask a)
forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Ordering
forall (a :: FlagType).
VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
min :: VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
$cmin :: forall (a :: FlagType).
VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
max :: VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
$cmax :: forall (a :: FlagType).
VkFormatFeatureBitmask a
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
>= :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
> :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
<= :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
< :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Bool
compare :: VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkFormatFeatureBitmask a)
Ord, Ptr b -> Int -> IO (VkFormatFeatureBitmask a)
Ptr b -> Int -> VkFormatFeatureBitmask a -> IO ()
Ptr (VkFormatFeatureBitmask a) -> IO (VkFormatFeatureBitmask a)
Ptr (VkFormatFeatureBitmask a)
-> Int -> IO (VkFormatFeatureBitmask a)
Ptr (VkFormatFeatureBitmask a)
-> Int -> VkFormatFeatureBitmask a -> IO ()
Ptr (VkFormatFeatureBitmask a) -> VkFormatFeatureBitmask a -> IO ()
VkFormatFeatureBitmask a -> Int
(VkFormatFeatureBitmask a -> Int)
-> (VkFormatFeatureBitmask a -> Int)
-> (Ptr (VkFormatFeatureBitmask a)
    -> Int -> IO (VkFormatFeatureBitmask a))
-> (Ptr (VkFormatFeatureBitmask a)
    -> Int -> VkFormatFeatureBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkFormatFeatureBitmask a))
-> (forall b. Ptr b -> Int -> VkFormatFeatureBitmask a -> IO ())
-> (Ptr (VkFormatFeatureBitmask a)
    -> IO (VkFormatFeatureBitmask a))
-> (Ptr (VkFormatFeatureBitmask a)
    -> VkFormatFeatureBitmask a -> IO ())
-> Storable (VkFormatFeatureBitmask a)
forall b. Ptr b -> Int -> IO (VkFormatFeatureBitmask a)
forall b. Ptr b -> Int -> VkFormatFeatureBitmask a -> 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
forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a) -> IO (VkFormatFeatureBitmask a)
forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a)
-> Int -> IO (VkFormatFeatureBitmask a)
forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a)
-> Int -> VkFormatFeatureBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a) -> VkFormatFeatureBitmask a -> IO ()
forall (a :: FlagType). VkFormatFeatureBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkFormatFeatureBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkFormatFeatureBitmask a -> IO ()
poke :: Ptr (VkFormatFeatureBitmask a) -> VkFormatFeatureBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a) -> VkFormatFeatureBitmask a -> IO ()
peek :: Ptr (VkFormatFeatureBitmask a) -> IO (VkFormatFeatureBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a) -> IO (VkFormatFeatureBitmask a)
pokeByteOff :: Ptr b -> Int -> VkFormatFeatureBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkFormatFeatureBitmask a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkFormatFeatureBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkFormatFeatureBitmask a)
pokeElemOff :: Ptr (VkFormatFeatureBitmask a)
-> Int -> VkFormatFeatureBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a)
-> Int -> VkFormatFeatureBitmask a -> IO ()
peekElemOff :: Ptr (VkFormatFeatureBitmask a)
-> Int -> IO (VkFormatFeatureBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkFormatFeatureBitmask a)
-> Int -> IO (VkFormatFeatureBitmask a)
alignment :: VkFormatFeatureBitmask a -> Int
$calignment :: forall (a :: FlagType). VkFormatFeatureBitmask a -> Int
sizeOf :: VkFormatFeatureBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkFormatFeatureBitmask a -> Int
Storable, Typeable (VkFormatFeatureBitmask a)
DataType
Constr
Typeable (VkFormatFeatureBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkFormatFeatureBitmask a
    -> c (VkFormatFeatureBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a))
-> (VkFormatFeatureBitmask a -> Constr)
-> (VkFormatFeatureBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkFormatFeatureBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkFormatFeatureBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkFormatFeatureBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkFormatFeatureBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a))
-> Data (VkFormatFeatureBitmask a)
VkFormatFeatureBitmask a -> DataType
VkFormatFeatureBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkFormatFeatureBitmask a
-> c (VkFormatFeatureBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkFormatFeatureBitmask a)
forall (a :: FlagType).
Typeable a =>
VkFormatFeatureBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkFormatFeatureBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkFormatFeatureBitmask a
-> c (VkFormatFeatureBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkFormatFeatureBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkFormatFeatureBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkFormatFeatureBitmask a
-> c (VkFormatFeatureBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkFormatFeatureBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkFormatFeatureBitmask a))
$cVkFormatFeatureBitmask :: Constr
$tVkFormatFeatureBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkFormatFeatureBitmask a -> m (VkFormatFeatureBitmask a)
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkFormatFeatureBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkFormatFeatureBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkFormatFeatureBitmask a -> VkFormatFeatureBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkFormatFeatureBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkFormatFeatureBitmask a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkFormatFeatureBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkFormatFeatureBitmask a))
dataTypeOf :: VkFormatFeatureBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkFormatFeatureBitmask a -> DataType
toConstr :: VkFormatFeatureBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkFormatFeatureBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkFormatFeatureBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkFormatFeatureBitmask a
-> c (VkFormatFeatureBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkFormatFeatureBitmask a
-> c (VkFormatFeatureBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkFormatFeatureBitmask a)
Data, (forall x.
 VkFormatFeatureBitmask a -> Rep (VkFormatFeatureBitmask a) x)
-> (forall x.
    Rep (VkFormatFeatureBitmask a) x -> VkFormatFeatureBitmask a)
-> Generic (VkFormatFeatureBitmask a)
forall x.
Rep (VkFormatFeatureBitmask a) x -> VkFormatFeatureBitmask a
forall x.
VkFormatFeatureBitmask a -> Rep (VkFormatFeatureBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkFormatFeatureBitmask a) x -> VkFormatFeatureBitmask a
forall (a :: FlagType) x.
VkFormatFeatureBitmask a -> Rep (VkFormatFeatureBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkFormatFeatureBitmask a) x -> VkFormatFeatureBitmask a
$cfrom :: forall (a :: FlagType) x.
VkFormatFeatureBitmask a -> Rep (VkFormatFeatureBitmask a) x
Generic)

type VkFormatFeatureFlags = VkFormatFeatureBitmask FlagMask

type VkFormatFeatureFlagBits = VkFormatFeatureBitmask FlagBit

pattern VkFormatFeatureFlagBits ::
        VkFlags -> VkFormatFeatureBitmask FlagBit

pattern $bVkFormatFeatureFlagBits :: VkFlags -> VkFormatFeatureBitmask FlagBit
$mVkFormatFeatureFlagBits :: forall r.
VkFormatFeatureBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkFormatFeatureFlagBits n = VkFormatFeatureBitmask n

pattern VkFormatFeatureFlags ::
        VkFlags -> VkFormatFeatureBitmask FlagMask

pattern $bVkFormatFeatureFlags :: VkFlags -> VkFormatFeatureBitmask FlagMask
$mVkFormatFeatureFlags :: forall r.
VkFormatFeatureBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkFormatFeatureFlags n = VkFormatFeatureBitmask n

deriving instance Bits (VkFormatFeatureBitmask FlagMask)

deriving instance FiniteBits (VkFormatFeatureBitmask FlagMask)

deriving instance Integral (VkFormatFeatureBitmask FlagMask)

deriving instance Num (VkFormatFeatureBitmask FlagMask)

deriving instance Bounded (VkFormatFeatureBitmask FlagMask)

deriving instance Enum (VkFormatFeatureBitmask FlagMask)

deriving instance Real (VkFormatFeatureBitmask FlagMask)

instance Show (VkFormatFeatureBitmask a) where
        showsPrec :: Int -> VkFormatFeatureBitmask a -> ShowS
showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_BLIT_SRC_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_BLIT_SRC_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_BLIT_DST_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_BLIT_DST_BIT"
        showsPrec Int
_ VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT
          = String -> ShowS
showString String
"VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT"
        showsPrec Int
p (VkFormatFeatureBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkFormatFeatureBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkFormatFeatureBitmask a) where
        readPrec :: ReadPrec (VkFormatFeatureBitmask a)
readPrec
          = ReadPrec (VkFormatFeatureBitmask a)
-> ReadPrec (VkFormatFeatureBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkFormatFeatureBitmask a))]
-> ReadPrec (VkFormatFeatureBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT),
                  (String
"VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT),
                  (String
"VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT),
                  (String
"VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT),
                  (String
"VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT),
                  (String
"VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT),
                  (String
"VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT),
                  (String
"VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT),
                  (String
"VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT),
                  (String
"VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT),
                  (String
"VK_FORMAT_FEATURE_BLIT_SRC_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_BLIT_SRC_BIT),
                  (String
"VK_FORMAT_FEATURE_BLIT_DST_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_BLIT_DST_BIT),
                  (String
"VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT",
                   VkFormatFeatureBitmask a -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkFormatFeatureBitmask a
forall (a :: FlagType). VkFormatFeatureBitmask a
VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT)]
                 ReadPrec (VkFormatFeatureBitmask a)
-> ReadPrec (VkFormatFeatureBitmask a)
-> ReadPrec (VkFormatFeatureBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkFormatFeatureBitmask a)
-> ReadPrec (VkFormatFeatureBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkFormatFeatureBitmask") ReadPrec ()
-> ReadPrec (VkFormatFeatureBitmask a)
-> ReadPrec (VkFormatFeatureBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkFormatFeatureBitmask a
forall (a :: FlagType). VkFlags -> VkFormatFeatureBitmask a
VkFormatFeatureBitmask (VkFlags -> VkFormatFeatureBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkFormatFeatureBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | Format can be used for sampled images (SAMPLED_IMAGE and COMBINED_IMAGE_SAMPLER descriptor types)
--
--   bitpos = @0@
pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_SAMPLED_IMAGE_BIT =
        VkFormatFeatureBitmask 1

-- | Format can be used for storage images (STORAGE_IMAGE descriptor type)
--
--   bitpos = @1@
pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_STORAGE_IMAGE_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_STORAGE_IMAGE_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_STORAGE_IMAGE_BIT =
        VkFormatFeatureBitmask 2

-- | Format supports atomic operations in case it is used for storage images
--
--   bitpos = @2@
pattern VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT =
        VkFormatFeatureBitmask 4

-- | Format can be used for uniform texel buffers (TBOs)
--
--   bitpos = @3@
pattern VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT =
        VkFormatFeatureBitmask 8

-- | Format can be used for storage texel buffers (IBOs)
--
--   bitpos = @4@
pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT =
        VkFormatFeatureBitmask 16

-- | Format supports atomic operations in case it is used for storage texel buffers
--
--   bitpos = @5@
pattern VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT =
        VkFormatFeatureBitmask 32

-- | Format can be used for vertex buffers (VBOs)
--
--   bitpos = @6@
pattern VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_VERTEX_BUFFER_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_VERTEX_BUFFER_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT =
        VkFormatFeatureBitmask 64

-- | Format can be used for color attachment images
--
--   bitpos = @7@
pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BIT =
        VkFormatFeatureBitmask 128

-- | Format supports blending in case it is used for color attachment images
--
--   bitpos = @8@
pattern VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT =
        VkFormatFeatureBitmask 256

-- | Format can be used for depth/stencil attachment images
--
--   bitpos = @9@
pattern VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT =
        VkFormatFeatureBitmask 512

-- | Format can be used as the source image of blits with vkCmdBlitImage
--
--   bitpos = @10@
pattern VK_FORMAT_FEATURE_BLIT_SRC_BIT :: VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_BLIT_SRC_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_BLIT_SRC_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_BLIT_SRC_BIT =
        VkFormatFeatureBitmask 1024

-- | Format can be used as the destination image of blits with vkCmdBlitImage
--
--   bitpos = @11@
pattern VK_FORMAT_FEATURE_BLIT_DST_BIT :: VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_BLIT_DST_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_BLIT_DST_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_BLIT_DST_BIT =
        VkFormatFeatureBitmask 2048

-- | Format can be filtered with VK_FILTER_LINEAR when being sampled
--
--   bitpos = @12@
pattern VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT ::
        VkFormatFeatureBitmask a

pattern $bVK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: VkFormatFeatureBitmask a
$mVK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: forall r (a :: FlagType).
VkFormatFeatureBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT =
        VkFormatFeatureBitmask 4096