{-# language CPP #-}
module Vulkan.Core10.Enums.Format  (Format( FORMAT_UNDEFINED
                                          , FORMAT_R4G4_UNORM_PACK8
                                          , FORMAT_R4G4B4A4_UNORM_PACK16
                                          , FORMAT_B4G4R4A4_UNORM_PACK16
                                          , FORMAT_R5G6B5_UNORM_PACK16
                                          , FORMAT_B5G6R5_UNORM_PACK16
                                          , FORMAT_R5G5B5A1_UNORM_PACK16
                                          , FORMAT_B5G5R5A1_UNORM_PACK16
                                          , FORMAT_A1R5G5B5_UNORM_PACK16
                                          , FORMAT_R8_UNORM
                                          , FORMAT_R8_SNORM
                                          , FORMAT_R8_USCALED
                                          , FORMAT_R8_SSCALED
                                          , FORMAT_R8_UINT
                                          , FORMAT_R8_SINT
                                          , FORMAT_R8_SRGB
                                          , FORMAT_R8G8_UNORM
                                          , FORMAT_R8G8_SNORM
                                          , FORMAT_R8G8_USCALED
                                          , FORMAT_R8G8_SSCALED
                                          , FORMAT_R8G8_UINT
                                          , FORMAT_R8G8_SINT
                                          , FORMAT_R8G8_SRGB
                                          , FORMAT_R8G8B8_UNORM
                                          , FORMAT_R8G8B8_SNORM
                                          , FORMAT_R8G8B8_USCALED
                                          , FORMAT_R8G8B8_SSCALED
                                          , FORMAT_R8G8B8_UINT
                                          , FORMAT_R8G8B8_SINT
                                          , FORMAT_R8G8B8_SRGB
                                          , FORMAT_B8G8R8_UNORM
                                          , FORMAT_B8G8R8_SNORM
                                          , FORMAT_B8G8R8_USCALED
                                          , FORMAT_B8G8R8_SSCALED
                                          , FORMAT_B8G8R8_UINT
                                          , FORMAT_B8G8R8_SINT
                                          , FORMAT_B8G8R8_SRGB
                                          , FORMAT_R8G8B8A8_UNORM
                                          , FORMAT_R8G8B8A8_SNORM
                                          , FORMAT_R8G8B8A8_USCALED
                                          , FORMAT_R8G8B8A8_SSCALED
                                          , FORMAT_R8G8B8A8_UINT
                                          , FORMAT_R8G8B8A8_SINT
                                          , FORMAT_R8G8B8A8_SRGB
                                          , FORMAT_B8G8R8A8_UNORM
                                          , FORMAT_B8G8R8A8_SNORM
                                          , FORMAT_B8G8R8A8_USCALED
                                          , FORMAT_B8G8R8A8_SSCALED
                                          , FORMAT_B8G8R8A8_UINT
                                          , FORMAT_B8G8R8A8_SINT
                                          , FORMAT_B8G8R8A8_SRGB
                                          , FORMAT_A8B8G8R8_UNORM_PACK32
                                          , FORMAT_A8B8G8R8_SNORM_PACK32
                                          , FORMAT_A8B8G8R8_USCALED_PACK32
                                          , FORMAT_A8B8G8R8_SSCALED_PACK32
                                          , FORMAT_A8B8G8R8_UINT_PACK32
                                          , FORMAT_A8B8G8R8_SINT_PACK32
                                          , FORMAT_A8B8G8R8_SRGB_PACK32
                                          , FORMAT_A2R10G10B10_UNORM_PACK32
                                          , FORMAT_A2R10G10B10_SNORM_PACK32
                                          , FORMAT_A2R10G10B10_USCALED_PACK32
                                          , FORMAT_A2R10G10B10_SSCALED_PACK32
                                          , FORMAT_A2R10G10B10_UINT_PACK32
                                          , FORMAT_A2R10G10B10_SINT_PACK32
                                          , FORMAT_A2B10G10R10_UNORM_PACK32
                                          , FORMAT_A2B10G10R10_SNORM_PACK32
                                          , FORMAT_A2B10G10R10_USCALED_PACK32
                                          , FORMAT_A2B10G10R10_SSCALED_PACK32
                                          , FORMAT_A2B10G10R10_UINT_PACK32
                                          , FORMAT_A2B10G10R10_SINT_PACK32
                                          , FORMAT_R16_UNORM
                                          , FORMAT_R16_SNORM
                                          , FORMAT_R16_USCALED
                                          , FORMAT_R16_SSCALED
                                          , FORMAT_R16_UINT
                                          , FORMAT_R16_SINT
                                          , FORMAT_R16_SFLOAT
                                          , FORMAT_R16G16_UNORM
                                          , FORMAT_R16G16_SNORM
                                          , FORMAT_R16G16_USCALED
                                          , FORMAT_R16G16_SSCALED
                                          , FORMAT_R16G16_UINT
                                          , FORMAT_R16G16_SINT
                                          , FORMAT_R16G16_SFLOAT
                                          , FORMAT_R16G16B16_UNORM
                                          , FORMAT_R16G16B16_SNORM
                                          , FORMAT_R16G16B16_USCALED
                                          , FORMAT_R16G16B16_SSCALED
                                          , FORMAT_R16G16B16_UINT
                                          , FORMAT_R16G16B16_SINT
                                          , FORMAT_R16G16B16_SFLOAT
                                          , FORMAT_R16G16B16A16_UNORM
                                          , FORMAT_R16G16B16A16_SNORM
                                          , FORMAT_R16G16B16A16_USCALED
                                          , FORMAT_R16G16B16A16_SSCALED
                                          , FORMAT_R16G16B16A16_UINT
                                          , FORMAT_R16G16B16A16_SINT
                                          , FORMAT_R16G16B16A16_SFLOAT
                                          , FORMAT_R32_UINT
                                          , FORMAT_R32_SINT
                                          , FORMAT_R32_SFLOAT
                                          , FORMAT_R32G32_UINT
                                          , FORMAT_R32G32_SINT
                                          , FORMAT_R32G32_SFLOAT
                                          , FORMAT_R32G32B32_UINT
                                          , FORMAT_R32G32B32_SINT
                                          , FORMAT_R32G32B32_SFLOAT
                                          , FORMAT_R32G32B32A32_UINT
                                          , FORMAT_R32G32B32A32_SINT
                                          , FORMAT_R32G32B32A32_SFLOAT
                                          , FORMAT_R64_UINT
                                          , FORMAT_R64_SINT
                                          , FORMAT_R64_SFLOAT
                                          , FORMAT_R64G64_UINT
                                          , FORMAT_R64G64_SINT
                                          , FORMAT_R64G64_SFLOAT
                                          , FORMAT_R64G64B64_UINT
                                          , FORMAT_R64G64B64_SINT
                                          , FORMAT_R64G64B64_SFLOAT
                                          , FORMAT_R64G64B64A64_UINT
                                          , FORMAT_R64G64B64A64_SINT
                                          , FORMAT_R64G64B64A64_SFLOAT
                                          , FORMAT_B10G11R11_UFLOAT_PACK32
                                          , FORMAT_E5B9G9R9_UFLOAT_PACK32
                                          , FORMAT_D16_UNORM
                                          , FORMAT_X8_D24_UNORM_PACK32
                                          , FORMAT_D32_SFLOAT
                                          , FORMAT_S8_UINT
                                          , FORMAT_D16_UNORM_S8_UINT
                                          , FORMAT_D24_UNORM_S8_UINT
                                          , FORMAT_D32_SFLOAT_S8_UINT
                                          , FORMAT_BC1_RGB_UNORM_BLOCK
                                          , FORMAT_BC1_RGB_SRGB_BLOCK
                                          , FORMAT_BC1_RGBA_UNORM_BLOCK
                                          , FORMAT_BC1_RGBA_SRGB_BLOCK
                                          , FORMAT_BC2_UNORM_BLOCK
                                          , FORMAT_BC2_SRGB_BLOCK
                                          , FORMAT_BC3_UNORM_BLOCK
                                          , FORMAT_BC3_SRGB_BLOCK
                                          , FORMAT_BC4_UNORM_BLOCK
                                          , FORMAT_BC4_SNORM_BLOCK
                                          , FORMAT_BC5_UNORM_BLOCK
                                          , FORMAT_BC5_SNORM_BLOCK
                                          , FORMAT_BC6H_UFLOAT_BLOCK
                                          , FORMAT_BC6H_SFLOAT_BLOCK
                                          , FORMAT_BC7_UNORM_BLOCK
                                          , FORMAT_BC7_SRGB_BLOCK
                                          , FORMAT_ETC2_R8G8B8_UNORM_BLOCK
                                          , FORMAT_ETC2_R8G8B8_SRGB_BLOCK
                                          , FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK
                                          , FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK
                                          , FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK
                                          , FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK
                                          , FORMAT_EAC_R11_UNORM_BLOCK
                                          , FORMAT_EAC_R11_SNORM_BLOCK
                                          , FORMAT_EAC_R11G11_UNORM_BLOCK
                                          , FORMAT_EAC_R11G11_SNORM_BLOCK
                                          , FORMAT_ASTC_4x4_UNORM_BLOCK
                                          , FORMAT_ASTC_4x4_SRGB_BLOCK
                                          , FORMAT_ASTC_5x4_UNORM_BLOCK
                                          , FORMAT_ASTC_5x4_SRGB_BLOCK
                                          , FORMAT_ASTC_5x5_UNORM_BLOCK
                                          , FORMAT_ASTC_5x5_SRGB_BLOCK
                                          , FORMAT_ASTC_6x5_UNORM_BLOCK
                                          , FORMAT_ASTC_6x5_SRGB_BLOCK
                                          , FORMAT_ASTC_6x6_UNORM_BLOCK
                                          , FORMAT_ASTC_6x6_SRGB_BLOCK
                                          , FORMAT_ASTC_8x5_UNORM_BLOCK
                                          , FORMAT_ASTC_8x5_SRGB_BLOCK
                                          , FORMAT_ASTC_8x6_UNORM_BLOCK
                                          , FORMAT_ASTC_8x6_SRGB_BLOCK
                                          , FORMAT_ASTC_8x8_UNORM_BLOCK
                                          , FORMAT_ASTC_8x8_SRGB_BLOCK
                                          , FORMAT_ASTC_10x5_UNORM_BLOCK
                                          , FORMAT_ASTC_10x5_SRGB_BLOCK
                                          , FORMAT_ASTC_10x6_UNORM_BLOCK
                                          , FORMAT_ASTC_10x6_SRGB_BLOCK
                                          , FORMAT_ASTC_10x8_UNORM_BLOCK
                                          , FORMAT_ASTC_10x8_SRGB_BLOCK
                                          , FORMAT_ASTC_10x10_UNORM_BLOCK
                                          , FORMAT_ASTC_10x10_SRGB_BLOCK
                                          , FORMAT_ASTC_12x10_UNORM_BLOCK
                                          , FORMAT_ASTC_12x10_SRGB_BLOCK
                                          , FORMAT_ASTC_12x12_UNORM_BLOCK
                                          , FORMAT_ASTC_12x12_SRGB_BLOCK
                                          , FORMAT_A4B4G4R4_UNORM_PACK16_EXT
                                          , FORMAT_A4R4G4B4_UNORM_PACK16_EXT
                                          , FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT
                                          , FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT
                                          , FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG
                                          , FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG
                                          , FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG
                                          , FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG
                                          , FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG
                                          , FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG
                                          , FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG
                                          , FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG
                                          , FORMAT_G16_B16_R16_3PLANE_444_UNORM
                                          , FORMAT_G16_B16R16_2PLANE_422_UNORM
                                          , FORMAT_G16_B16_R16_3PLANE_422_UNORM
                                          , FORMAT_G16_B16R16_2PLANE_420_UNORM
                                          , FORMAT_G16_B16_R16_3PLANE_420_UNORM
                                          , FORMAT_B16G16R16G16_422_UNORM
                                          , FORMAT_G16B16G16R16_422_UNORM
                                          , FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16
                                          , FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16
                                          , FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16
                                          , FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16
                                          , FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16
                                          , FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16
                                          , FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16
                                          , FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16
                                          , FORMAT_R12X4G12X4_UNORM_2PACK16
                                          , FORMAT_R12X4_UNORM_PACK16
                                          , FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16
                                          , FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16
                                          , FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16
                                          , FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16
                                          , FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16
                                          , FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16
                                          , FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16
                                          , FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16
                                          , FORMAT_R10X6G10X6_UNORM_2PACK16
                                          , FORMAT_R10X6_UNORM_PACK16
                                          , FORMAT_G8_B8_R8_3PLANE_444_UNORM
                                          , FORMAT_G8_B8R8_2PLANE_422_UNORM
                                          , FORMAT_G8_B8_R8_3PLANE_422_UNORM
                                          , FORMAT_G8_B8R8_2PLANE_420_UNORM
                                          , FORMAT_G8_B8_R8_3PLANE_420_UNORM
                                          , FORMAT_B8G8R8G8_422_UNORM
                                          , FORMAT_G8B8G8R8_422_UNORM
                                          , ..
                                          )) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
-- | VkFormat - Available image formats
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.AccelerationStructureCreateGeometryTypeInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.AccelerationStructureGeometryTrianglesDataKHR',
-- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferFormatPropertiesANDROID',
-- 'Vulkan.Core10.Pass.AttachmentDescription',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2',
-- 'Vulkan.Core10.BufferView.BufferViewCreateInfo',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentImageInfo',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.GeometryTrianglesNV',
-- 'Vulkan.Core10.Image.ImageCreateInfo',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo',
-- 'Vulkan.Extensions.VK_EXT_astc_decode_mode.ImageViewASTCDecodeModeEXT',
-- 'Vulkan.Core10.ImageView.ImageViewCreateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceImageFormatInfo2',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceSparseImageFormatInfo2',
-- 'Vulkan.Extensions.VK_EXT_custom_border_color.SamplerCustomBorderColorCreateInfoEXT',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo',
-- 'Vulkan.Extensions.VK_KHR_surface.SurfaceFormatKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR',
-- 'Vulkan.Core10.Pipeline.VertexInputAttributeDescription',
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.getPhysicalDeviceExternalImageFormatPropertiesNV',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2KHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.getPhysicalDeviceSparseImageFormatProperties'
newtype Format = Format Int32
  deriving newtype (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
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 :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmax :: Format -> Format -> Format
>= :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c< :: Format -> Format -> Bool
compare :: Format -> Format -> Ordering
$ccompare :: Format -> Format -> Ordering
$cp1Ord :: Eq Format
Ord, Ptr b -> Int -> IO Format
Ptr b -> Int -> Format -> IO ()
Ptr Format -> IO Format
Ptr Format -> Int -> IO Format
Ptr Format -> Int -> Format -> IO ()
Ptr Format -> Format -> IO ()
Format -> Int
(Format -> Int)
-> (Format -> Int)
-> (Ptr Format -> Int -> IO Format)
-> (Ptr Format -> Int -> Format -> IO ())
-> (forall b. Ptr b -> Int -> IO Format)
-> (forall b. Ptr b -> Int -> Format -> IO ())
-> (Ptr Format -> IO Format)
-> (Ptr Format -> Format -> IO ())
-> Storable Format
forall b. Ptr b -> Int -> IO Format
forall b. Ptr b -> Int -> Format -> 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 Format -> Format -> IO ()
$cpoke :: Ptr Format -> Format -> IO ()
peek :: Ptr Format -> IO Format
$cpeek :: Ptr Format -> IO Format
pokeByteOff :: Ptr b -> Int -> Format -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Format -> IO ()
peekByteOff :: Ptr b -> Int -> IO Format
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Format
pokeElemOff :: Ptr Format -> Int -> Format -> IO ()
$cpokeElemOff :: Ptr Format -> Int -> Format -> IO ()
peekElemOff :: Ptr Format -> Int -> IO Format
$cpeekElemOff :: Ptr Format -> Int -> IO Format
alignment :: Format -> Int
$calignment :: Format -> Int
sizeOf :: Format -> Int
$csizeOf :: Format -> Int
Storable, Format
Format -> Zero Format
forall a. a -> Zero a
zero :: Format
$czero :: Format
Zero)

-- | 'FORMAT_UNDEFINED' specifies that the format is not specified.
pattern $bFORMAT_UNDEFINED :: Format
$mFORMAT_UNDEFINED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_UNDEFINED = Format 0
-- | 'FORMAT_R4G4_UNORM_PACK8' specifies a two-component, 8-bit packed
-- unsigned normalized format that has a 4-bit R component in bits 4..7,
-- and a 4-bit G component in bits 0..3.
pattern $bFORMAT_R4G4_UNORM_PACK8 :: Format
$mFORMAT_R4G4_UNORM_PACK8 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R4G4_UNORM_PACK8 = Format 1
-- | 'FORMAT_R4G4B4A4_UNORM_PACK16' specifies a four-component, 16-bit packed
-- unsigned normalized format that has a 4-bit R component in bits 12..15,
-- a 4-bit G component in bits 8..11, a 4-bit B component in bits 4..7, and
-- a 4-bit A component in bits 0..3.
pattern $bFORMAT_R4G4B4A4_UNORM_PACK16 :: Format
$mFORMAT_R4G4B4A4_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R4G4B4A4_UNORM_PACK16 = Format 2
-- | 'FORMAT_B4G4R4A4_UNORM_PACK16' specifies a four-component, 16-bit packed
-- unsigned normalized format that has a 4-bit B component in bits 12..15,
-- a 4-bit G component in bits 8..11, a 4-bit R component in bits 4..7, and
-- a 4-bit A component in bits 0..3.
pattern $bFORMAT_B4G4R4A4_UNORM_PACK16 :: Format
$mFORMAT_B4G4R4A4_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B4G4R4A4_UNORM_PACK16 = Format 3
-- | 'FORMAT_R5G6B5_UNORM_PACK16' specifies a three-component, 16-bit packed
-- unsigned normalized format that has a 5-bit R component in bits 11..15,
-- a 6-bit G component in bits 5..10, and a 5-bit B component in bits 0..4.
pattern $bFORMAT_R5G6B5_UNORM_PACK16 :: Format
$mFORMAT_R5G6B5_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R5G6B5_UNORM_PACK16 = Format 4
-- | 'FORMAT_B5G6R5_UNORM_PACK16' specifies a three-component, 16-bit packed
-- unsigned normalized format that has a 5-bit B component in bits 11..15,
-- a 6-bit G component in bits 5..10, and a 5-bit R component in bits 0..4.
pattern $bFORMAT_B5G6R5_UNORM_PACK16 :: Format
$mFORMAT_B5G6R5_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B5G6R5_UNORM_PACK16 = Format 5
-- | 'FORMAT_R5G5B5A1_UNORM_PACK16' specifies a four-component, 16-bit packed
-- unsigned normalized format that has a 5-bit R component in bits 11..15,
-- a 5-bit G component in bits 6..10, a 5-bit B component in bits 1..5, and
-- a 1-bit A component in bit 0.
pattern $bFORMAT_R5G5B5A1_UNORM_PACK16 :: Format
$mFORMAT_R5G5B5A1_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R5G5B5A1_UNORM_PACK16 = Format 6
-- | 'FORMAT_B5G5R5A1_UNORM_PACK16' specifies a four-component, 16-bit packed
-- unsigned normalized format that has a 5-bit B component in bits 11..15,
-- a 5-bit G component in bits 6..10, a 5-bit R component in bits 1..5, and
-- a 1-bit A component in bit 0.
pattern $bFORMAT_B5G5R5A1_UNORM_PACK16 :: Format
$mFORMAT_B5G5R5A1_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B5G5R5A1_UNORM_PACK16 = Format 7
-- | 'FORMAT_A1R5G5B5_UNORM_PACK16' specifies a four-component, 16-bit packed
-- unsigned normalized format that has a 1-bit A component in bit 15, a
-- 5-bit R component in bits 10..14, a 5-bit G component in bits 5..9, and
-- a 5-bit B component in bits 0..4.
pattern $bFORMAT_A1R5G5B5_UNORM_PACK16 :: Format
$mFORMAT_A1R5G5B5_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A1R5G5B5_UNORM_PACK16 = Format 8
-- | 'FORMAT_R8_UNORM' specifies a one-component, 8-bit unsigned normalized
-- format that has a single 8-bit R component.
pattern $bFORMAT_R8_UNORM :: Format
$mFORMAT_R8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_UNORM = Format 9
-- | 'FORMAT_R8_SNORM' specifies a one-component, 8-bit signed normalized
-- format that has a single 8-bit R component.
pattern $bFORMAT_R8_SNORM :: Format
$mFORMAT_R8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_SNORM = Format 10
-- | 'FORMAT_R8_USCALED' specifies a one-component, 8-bit unsigned scaled
-- integer format that has a single 8-bit R component.
pattern $bFORMAT_R8_USCALED :: Format
$mFORMAT_R8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_USCALED = Format 11
-- | 'FORMAT_R8_SSCALED' specifies a one-component, 8-bit signed scaled
-- integer format that has a single 8-bit R component.
pattern $bFORMAT_R8_SSCALED :: Format
$mFORMAT_R8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_SSCALED = Format 12
-- | 'FORMAT_R8_UINT' specifies a one-component, 8-bit unsigned integer
-- format that has a single 8-bit R component.
pattern $bFORMAT_R8_UINT :: Format
$mFORMAT_R8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_UINT = Format 13
-- | 'FORMAT_R8_SINT' specifies a one-component, 8-bit signed integer format
-- that has a single 8-bit R component.
pattern $bFORMAT_R8_SINT :: Format
$mFORMAT_R8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_SINT = Format 14
-- | 'FORMAT_R8_SRGB' specifies a one-component, 8-bit unsigned normalized
-- format that has a single 8-bit R component stored with sRGB nonlinear
-- encoding.
pattern $bFORMAT_R8_SRGB :: Format
$mFORMAT_R8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8_SRGB = Format 15
-- | 'FORMAT_R8G8_UNORM' specifies a two-component, 16-bit unsigned
-- normalized format that has an 8-bit R component in byte 0, and an 8-bit
-- G component in byte 1.
pattern $bFORMAT_R8G8_UNORM :: Format
$mFORMAT_R8G8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_UNORM = Format 16
-- | 'FORMAT_R8G8_SNORM' specifies a two-component, 16-bit signed normalized
-- format that has an 8-bit R component in byte 0, and an 8-bit G component
-- in byte 1.
pattern $bFORMAT_R8G8_SNORM :: Format
$mFORMAT_R8G8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_SNORM = Format 17
-- | 'FORMAT_R8G8_USCALED' specifies a two-component, 16-bit unsigned scaled
-- integer format that has an 8-bit R component in byte 0, and an 8-bit G
-- component in byte 1.
pattern $bFORMAT_R8G8_USCALED :: Format
$mFORMAT_R8G8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_USCALED = Format 18
-- | 'FORMAT_R8G8_SSCALED' specifies a two-component, 16-bit signed scaled
-- integer format that has an 8-bit R component in byte 0, and an 8-bit G
-- component in byte 1.
pattern $bFORMAT_R8G8_SSCALED :: Format
$mFORMAT_R8G8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_SSCALED = Format 19
-- | 'FORMAT_R8G8_UINT' specifies a two-component, 16-bit unsigned integer
-- format that has an 8-bit R component in byte 0, and an 8-bit G component
-- in byte 1.
pattern $bFORMAT_R8G8_UINT :: Format
$mFORMAT_R8G8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_UINT = Format 20
-- | 'FORMAT_R8G8_SINT' specifies a two-component, 16-bit signed integer
-- format that has an 8-bit R component in byte 0, and an 8-bit G component
-- in byte 1.
pattern $bFORMAT_R8G8_SINT :: Format
$mFORMAT_R8G8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_SINT = Format 21
-- | 'FORMAT_R8G8_SRGB' specifies a two-component, 16-bit unsigned normalized
-- format that has an 8-bit R component stored with sRGB nonlinear encoding
-- in byte 0, and an 8-bit G component stored with sRGB nonlinear encoding
-- in byte 1.
pattern $bFORMAT_R8G8_SRGB :: Format
$mFORMAT_R8G8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8_SRGB = Format 22
-- | 'FORMAT_R8G8B8_UNORM' specifies a three-component, 24-bit unsigned
-- normalized format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_UNORM :: Format
$mFORMAT_R8G8B8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_UNORM = Format 23
-- | 'FORMAT_R8G8B8_SNORM' specifies a three-component, 24-bit signed
-- normalized format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_SNORM :: Format
$mFORMAT_R8G8B8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_SNORM = Format 24
-- | 'FORMAT_R8G8B8_USCALED' specifies a three-component, 24-bit unsigned
-- scaled format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_USCALED :: Format
$mFORMAT_R8G8B8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_USCALED = Format 25
-- | 'FORMAT_R8G8B8_SSCALED' specifies a three-component, 24-bit signed
-- scaled format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_SSCALED :: Format
$mFORMAT_R8G8B8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_SSCALED = Format 26
-- | 'FORMAT_R8G8B8_UINT' specifies a three-component, 24-bit unsigned
-- integer format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_UINT :: Format
$mFORMAT_R8G8B8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_UINT = Format 27
-- | 'FORMAT_R8G8B8_SINT' specifies a three-component, 24-bit signed integer
-- format that has an 8-bit R component in byte 0, an 8-bit G component in
-- byte 1, and an 8-bit B component in byte 2.
pattern $bFORMAT_R8G8B8_SINT :: Format
$mFORMAT_R8G8B8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_SINT = Format 28
-- | 'FORMAT_R8G8B8_SRGB' specifies a three-component, 24-bit unsigned
-- normalized format that has an 8-bit R component stored with sRGB
-- nonlinear encoding in byte 0, an 8-bit G component stored with sRGB
-- nonlinear encoding in byte 1, and an 8-bit B component stored with sRGB
-- nonlinear encoding in byte 2.
pattern $bFORMAT_R8G8B8_SRGB :: Format
$mFORMAT_R8G8B8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8_SRGB = Format 29
-- | 'FORMAT_B8G8R8_UNORM' specifies a three-component, 24-bit unsigned
-- normalized format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_UNORM :: Format
$mFORMAT_B8G8R8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_UNORM = Format 30
-- | 'FORMAT_B8G8R8_SNORM' specifies a three-component, 24-bit signed
-- normalized format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_SNORM :: Format
$mFORMAT_B8G8R8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_SNORM = Format 31
-- | 'FORMAT_B8G8R8_USCALED' specifies a three-component, 24-bit unsigned
-- scaled format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_USCALED :: Format
$mFORMAT_B8G8R8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_USCALED = Format 32
-- | 'FORMAT_B8G8R8_SSCALED' specifies a three-component, 24-bit signed
-- scaled format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_SSCALED :: Format
$mFORMAT_B8G8R8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_SSCALED = Format 33
-- | 'FORMAT_B8G8R8_UINT' specifies a three-component, 24-bit unsigned
-- integer format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_UINT :: Format
$mFORMAT_B8G8R8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_UINT = Format 34
-- | 'FORMAT_B8G8R8_SINT' specifies a three-component, 24-bit signed integer
-- format that has an 8-bit B component in byte 0, an 8-bit G component in
-- byte 1, and an 8-bit R component in byte 2.
pattern $bFORMAT_B8G8R8_SINT :: Format
$mFORMAT_B8G8R8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_SINT = Format 35
-- | 'FORMAT_B8G8R8_SRGB' specifies a three-component, 24-bit unsigned
-- normalized format that has an 8-bit B component stored with sRGB
-- nonlinear encoding in byte 0, an 8-bit G component stored with sRGB
-- nonlinear encoding in byte 1, and an 8-bit R component stored with sRGB
-- nonlinear encoding in byte 2.
pattern $bFORMAT_B8G8R8_SRGB :: Format
$mFORMAT_B8G8R8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8_SRGB = Format 36
-- | 'FORMAT_R8G8B8A8_UNORM' specifies a four-component, 32-bit unsigned
-- normalized format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit B component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_R8G8B8A8_UNORM :: Format
$mFORMAT_R8G8B8A8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_UNORM = Format 37
-- | 'FORMAT_R8G8B8A8_SNORM' specifies a four-component, 32-bit signed
-- normalized format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit B component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_R8G8B8A8_SNORM :: Format
$mFORMAT_R8G8B8A8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_SNORM = Format 38
-- | 'FORMAT_R8G8B8A8_USCALED' specifies a four-component, 32-bit unsigned
-- scaled format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit B component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_R8G8B8A8_USCALED :: Format
$mFORMAT_R8G8B8A8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_USCALED = Format 39
-- | 'FORMAT_R8G8B8A8_SSCALED' specifies a four-component, 32-bit signed
-- scaled format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit B component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_R8G8B8A8_SSCALED :: Format
$mFORMAT_R8G8B8A8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_SSCALED = Format 40
-- | 'FORMAT_R8G8B8A8_UINT' specifies a four-component, 32-bit unsigned
-- integer format that has an 8-bit R component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit B component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_R8G8B8A8_UINT :: Format
$mFORMAT_R8G8B8A8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_UINT = Format 41
-- | 'FORMAT_R8G8B8A8_SINT' specifies a four-component, 32-bit signed integer
-- format that has an 8-bit R component in byte 0, an 8-bit G component in
-- byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte
-- 3.
pattern $bFORMAT_R8G8B8A8_SINT :: Format
$mFORMAT_R8G8B8A8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_SINT = Format 42
-- | 'FORMAT_R8G8B8A8_SRGB' specifies a four-component, 32-bit unsigned
-- normalized format that has an 8-bit R component stored with sRGB
-- nonlinear encoding in byte 0, an 8-bit G component stored with sRGB
-- nonlinear encoding in byte 1, an 8-bit B component stored with sRGB
-- nonlinear encoding in byte 2, and an 8-bit A component in byte 3.
pattern $bFORMAT_R8G8B8A8_SRGB :: Format
$mFORMAT_R8G8B8A8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R8G8B8A8_SRGB = Format 43
-- | 'FORMAT_B8G8R8A8_UNORM' specifies a four-component, 32-bit unsigned
-- normalized format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit R component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_B8G8R8A8_UNORM :: Format
$mFORMAT_B8G8R8A8_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_UNORM = Format 44
-- | 'FORMAT_B8G8R8A8_SNORM' specifies a four-component, 32-bit signed
-- normalized format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit R component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_B8G8R8A8_SNORM :: Format
$mFORMAT_B8G8R8A8_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_SNORM = Format 45
-- | 'FORMAT_B8G8R8A8_USCALED' specifies a four-component, 32-bit unsigned
-- scaled format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit R component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_B8G8R8A8_USCALED :: Format
$mFORMAT_B8G8R8A8_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_USCALED = Format 46
-- | 'FORMAT_B8G8R8A8_SSCALED' specifies a four-component, 32-bit signed
-- scaled format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit R component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_B8G8R8A8_SSCALED :: Format
$mFORMAT_B8G8R8A8_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_SSCALED = Format 47
-- | 'FORMAT_B8G8R8A8_UINT' specifies a four-component, 32-bit unsigned
-- integer format that has an 8-bit B component in byte 0, an 8-bit G
-- component in byte 1, an 8-bit R component in byte 2, and an 8-bit A
-- component in byte 3.
pattern $bFORMAT_B8G8R8A8_UINT :: Format
$mFORMAT_B8G8R8A8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_UINT = Format 48
-- | 'FORMAT_B8G8R8A8_SINT' specifies a four-component, 32-bit signed integer
-- format that has an 8-bit B component in byte 0, an 8-bit G component in
-- byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte
-- 3.
pattern $bFORMAT_B8G8R8A8_SINT :: Format
$mFORMAT_B8G8R8A8_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_SINT = Format 49
-- | 'FORMAT_B8G8R8A8_SRGB' specifies a four-component, 32-bit unsigned
-- normalized format that has an 8-bit B component stored with sRGB
-- nonlinear encoding in byte 0, an 8-bit G component stored with sRGB
-- nonlinear encoding in byte 1, an 8-bit R component stored with sRGB
-- nonlinear encoding in byte 2, and an 8-bit A component in byte 3.
pattern $bFORMAT_B8G8R8A8_SRGB :: Format
$mFORMAT_B8G8R8A8_SRGB :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8A8_SRGB = Format 50
-- | 'FORMAT_A8B8G8R8_UNORM_PACK32' specifies a four-component, 32-bit packed
-- unsigned normalized format that has an 8-bit A component in bits 24..31,
-- an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15,
-- and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_UNORM_PACK32 :: Format
$mFORMAT_A8B8G8R8_UNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_UNORM_PACK32 = Format 51
-- | 'FORMAT_A8B8G8R8_SNORM_PACK32' specifies a four-component, 32-bit packed
-- signed normalized format that has an 8-bit A component in bits 24..31,
-- an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15,
-- and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_SNORM_PACK32 :: Format
$mFORMAT_A8B8G8R8_SNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_SNORM_PACK32 = Format 52
-- | 'FORMAT_A8B8G8R8_USCALED_PACK32' specifies a four-component, 32-bit
-- packed unsigned scaled integer format that has an 8-bit A component in
-- bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component
-- in bits 8..15, and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_USCALED_PACK32 :: Format
$mFORMAT_A8B8G8R8_USCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_USCALED_PACK32 = Format 53
-- | 'FORMAT_A8B8G8R8_SSCALED_PACK32' specifies a four-component, 32-bit
-- packed signed scaled integer format that has an 8-bit A component in
-- bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component
-- in bits 8..15, and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_SSCALED_PACK32 :: Format
$mFORMAT_A8B8G8R8_SSCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_SSCALED_PACK32 = Format 54
-- | 'FORMAT_A8B8G8R8_UINT_PACK32' specifies a four-component, 32-bit packed
-- unsigned integer format that has an 8-bit A component in bits 24..31, an
-- 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15,
-- and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_UINT_PACK32 :: Format
$mFORMAT_A8B8G8R8_UINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_UINT_PACK32 = Format 55
-- | 'FORMAT_A8B8G8R8_SINT_PACK32' specifies a four-component, 32-bit packed
-- signed integer format that has an 8-bit A component in bits 24..31, an
-- 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15,
-- and an 8-bit R component in bits 0..7.
pattern $bFORMAT_A8B8G8R8_SINT_PACK32 :: Format
$mFORMAT_A8B8G8R8_SINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_SINT_PACK32 = Format 56
-- | 'FORMAT_A8B8G8R8_SRGB_PACK32' specifies a four-component, 32-bit packed
-- unsigned normalized format that has an 8-bit A component in bits 24..31,
-- an 8-bit B component stored with sRGB nonlinear encoding in bits 16..23,
-- an 8-bit G component stored with sRGB nonlinear encoding in bits 8..15,
-- and an 8-bit R component stored with sRGB nonlinear encoding in bits
-- 0..7.
pattern $bFORMAT_A8B8G8R8_SRGB_PACK32 :: Format
$mFORMAT_A8B8G8R8_SRGB_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A8B8G8R8_SRGB_PACK32 = Format 57
-- | 'FORMAT_A2R10G10B10_UNORM_PACK32' specifies a four-component, 32-bit
-- packed unsigned normalized format that has a 2-bit A component in bits
-- 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_UNORM_PACK32 :: Format
$mFORMAT_A2R10G10B10_UNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_UNORM_PACK32 = Format 58
-- | 'FORMAT_A2R10G10B10_SNORM_PACK32' specifies a four-component, 32-bit
-- packed signed normalized format that has a 2-bit A component in bits
-- 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_SNORM_PACK32 :: Format
$mFORMAT_A2R10G10B10_SNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_SNORM_PACK32 = Format 59
-- | 'FORMAT_A2R10G10B10_USCALED_PACK32' specifies a four-component, 32-bit
-- packed unsigned scaled integer format that has a 2-bit A component in
-- bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component
-- in bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_USCALED_PACK32 :: Format
$mFORMAT_A2R10G10B10_USCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_USCALED_PACK32 = Format 60
-- | 'FORMAT_A2R10G10B10_SSCALED_PACK32' specifies a four-component, 32-bit
-- packed signed scaled integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_SSCALED_PACK32 :: Format
$mFORMAT_A2R10G10B10_SSCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_SSCALED_PACK32 = Format 61
-- | 'FORMAT_A2R10G10B10_UINT_PACK32' specifies a four-component, 32-bit
-- packed unsigned integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_UINT_PACK32 :: Format
$mFORMAT_A2R10G10B10_UINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_UINT_PACK32 = Format 62
-- | 'FORMAT_A2R10G10B10_SINT_PACK32' specifies a four-component, 32-bit
-- packed signed integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit B component in bits 0..9.
pattern $bFORMAT_A2R10G10B10_SINT_PACK32 :: Format
$mFORMAT_A2R10G10B10_SINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2R10G10B10_SINT_PACK32 = Format 63
-- | 'FORMAT_A2B10G10R10_UNORM_PACK32' specifies a four-component, 32-bit
-- packed unsigned normalized format that has a 2-bit A component in bits
-- 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_UNORM_PACK32 :: Format
$mFORMAT_A2B10G10R10_UNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_UNORM_PACK32 = Format 64
-- | 'FORMAT_A2B10G10R10_SNORM_PACK32' specifies a four-component, 32-bit
-- packed signed normalized format that has a 2-bit A component in bits
-- 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_SNORM_PACK32 :: Format
$mFORMAT_A2B10G10R10_SNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_SNORM_PACK32 = Format 65
-- | 'FORMAT_A2B10G10R10_USCALED_PACK32' specifies a four-component, 32-bit
-- packed unsigned scaled integer format that has a 2-bit A component in
-- bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component
-- in bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_USCALED_PACK32 :: Format
$mFORMAT_A2B10G10R10_USCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_USCALED_PACK32 = Format 66
-- | 'FORMAT_A2B10G10R10_SSCALED_PACK32' specifies a four-component, 32-bit
-- packed signed scaled integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_SSCALED_PACK32 :: Format
$mFORMAT_A2B10G10R10_SSCALED_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_SSCALED_PACK32 = Format 67
-- | 'FORMAT_A2B10G10R10_UINT_PACK32' specifies a four-component, 32-bit
-- packed unsigned integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_UINT_PACK32 :: Format
$mFORMAT_A2B10G10R10_UINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_UINT_PACK32 = Format 68
-- | 'FORMAT_A2B10G10R10_SINT_PACK32' specifies a four-component, 32-bit
-- packed signed integer format that has a 2-bit A component in bits
-- 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in
-- bits 10..19, and a 10-bit R component in bits 0..9.
pattern $bFORMAT_A2B10G10R10_SINT_PACK32 :: Format
$mFORMAT_A2B10G10R10_SINT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A2B10G10R10_SINT_PACK32 = Format 69
-- | 'FORMAT_R16_UNORM' specifies a one-component, 16-bit unsigned normalized
-- format that has a single 16-bit R component.
pattern $bFORMAT_R16_UNORM :: Format
$mFORMAT_R16_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_UNORM = Format 70
-- | 'FORMAT_R16_SNORM' specifies a one-component, 16-bit signed normalized
-- format that has a single 16-bit R component.
pattern $bFORMAT_R16_SNORM :: Format
$mFORMAT_R16_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_SNORM = Format 71
-- | 'FORMAT_R16_USCALED' specifies a one-component, 16-bit unsigned scaled
-- integer format that has a single 16-bit R component.
pattern $bFORMAT_R16_USCALED :: Format
$mFORMAT_R16_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_USCALED = Format 72
-- | 'FORMAT_R16_SSCALED' specifies a one-component, 16-bit signed scaled
-- integer format that has a single 16-bit R component.
pattern $bFORMAT_R16_SSCALED :: Format
$mFORMAT_R16_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_SSCALED = Format 73
-- | 'FORMAT_R16_UINT' specifies a one-component, 16-bit unsigned integer
-- format that has a single 16-bit R component.
pattern $bFORMAT_R16_UINT :: Format
$mFORMAT_R16_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_UINT = Format 74
-- | 'FORMAT_R16_SINT' specifies a one-component, 16-bit signed integer
-- format that has a single 16-bit R component.
pattern $bFORMAT_R16_SINT :: Format
$mFORMAT_R16_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_SINT = Format 75
-- | 'FORMAT_R16_SFLOAT' specifies a one-component, 16-bit signed
-- floating-point format that has a single 16-bit R component.
pattern $bFORMAT_R16_SFLOAT :: Format
$mFORMAT_R16_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16_SFLOAT = Format 76
-- | 'FORMAT_R16G16_UNORM' specifies a two-component, 32-bit unsigned
-- normalized format that has a 16-bit R component in bytes 0..1, and a
-- 16-bit G component in bytes 2..3.
pattern $bFORMAT_R16G16_UNORM :: Format
$mFORMAT_R16G16_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_UNORM = Format 77
-- | 'FORMAT_R16G16_SNORM' specifies a two-component, 32-bit signed
-- normalized format that has a 16-bit R component in bytes 0..1, and a
-- 16-bit G component in bytes 2..3.
pattern $bFORMAT_R16G16_SNORM :: Format
$mFORMAT_R16G16_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_SNORM = Format 78
-- | 'FORMAT_R16G16_USCALED' specifies a two-component, 32-bit unsigned
-- scaled integer format that has a 16-bit R component in bytes 0..1, and a
-- 16-bit G component in bytes 2..3.
pattern $bFORMAT_R16G16_USCALED :: Format
$mFORMAT_R16G16_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_USCALED = Format 79
-- | 'FORMAT_R16G16_SSCALED' specifies a two-component, 32-bit signed scaled
-- integer format that has a 16-bit R component in bytes 0..1, and a 16-bit
-- G component in bytes 2..3.
pattern $bFORMAT_R16G16_SSCALED :: Format
$mFORMAT_R16G16_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_SSCALED = Format 80
-- | 'FORMAT_R16G16_UINT' specifies a two-component, 32-bit unsigned integer
-- format that has a 16-bit R component in bytes 0..1, and a 16-bit G
-- component in bytes 2..3.
pattern $bFORMAT_R16G16_UINT :: Format
$mFORMAT_R16G16_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_UINT = Format 81
-- | 'FORMAT_R16G16_SINT' specifies a two-component, 32-bit signed integer
-- format that has a 16-bit R component in bytes 0..1, and a 16-bit G
-- component in bytes 2..3.
pattern $bFORMAT_R16G16_SINT :: Format
$mFORMAT_R16G16_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_SINT = Format 82
-- | 'FORMAT_R16G16_SFLOAT' specifies a two-component, 32-bit signed
-- floating-point format that has a 16-bit R component in bytes 0..1, and a
-- 16-bit G component in bytes 2..3.
pattern $bFORMAT_R16G16_SFLOAT :: Format
$mFORMAT_R16G16_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16_SFLOAT = Format 83
-- | 'FORMAT_R16G16B16_UNORM' specifies a three-component, 48-bit unsigned
-- normalized format that has a 16-bit R component in bytes 0..1, a 16-bit
-- G component in bytes 2..3, and a 16-bit B component in bytes 4..5.
pattern $bFORMAT_R16G16B16_UNORM :: Format
$mFORMAT_R16G16B16_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_UNORM = Format 84
-- | 'FORMAT_R16G16B16_SNORM' specifies a three-component, 48-bit signed
-- normalized format that has a 16-bit R component in bytes 0..1, a 16-bit
-- G component in bytes 2..3, and a 16-bit B component in bytes 4..5.
pattern $bFORMAT_R16G16B16_SNORM :: Format
$mFORMAT_R16G16B16_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_SNORM = Format 85
-- | 'FORMAT_R16G16B16_USCALED' specifies a three-component, 48-bit unsigned
-- scaled integer format that has a 16-bit R component in bytes 0..1, a
-- 16-bit G component in bytes 2..3, and a 16-bit B component in bytes
-- 4..5.
pattern $bFORMAT_R16G16B16_USCALED :: Format
$mFORMAT_R16G16B16_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_USCALED = Format 86
-- | 'FORMAT_R16G16B16_SSCALED' specifies a three-component, 48-bit signed
-- scaled integer format that has a 16-bit R component in bytes 0..1, a
-- 16-bit G component in bytes 2..3, and a 16-bit B component in bytes
-- 4..5.
pattern $bFORMAT_R16G16B16_SSCALED :: Format
$mFORMAT_R16G16B16_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_SSCALED = Format 87
-- | 'FORMAT_R16G16B16_UINT' specifies a three-component, 48-bit unsigned
-- integer format that has a 16-bit R component in bytes 0..1, a 16-bit G
-- component in bytes 2..3, and a 16-bit B component in bytes 4..5.
pattern $bFORMAT_R16G16B16_UINT :: Format
$mFORMAT_R16G16B16_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_UINT = Format 88
-- | 'FORMAT_R16G16B16_SINT' specifies a three-component, 48-bit signed
-- integer format that has a 16-bit R component in bytes 0..1, a 16-bit G
-- component in bytes 2..3, and a 16-bit B component in bytes 4..5.
pattern $bFORMAT_R16G16B16_SINT :: Format
$mFORMAT_R16G16B16_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_SINT = Format 89
-- | 'FORMAT_R16G16B16_SFLOAT' specifies a three-component, 48-bit signed
-- floating-point format that has a 16-bit R component in bytes 0..1, a
-- 16-bit G component in bytes 2..3, and a 16-bit B component in bytes
-- 4..5.
pattern $bFORMAT_R16G16B16_SFLOAT :: Format
$mFORMAT_R16G16B16_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16_SFLOAT = Format 90
-- | 'FORMAT_R16G16B16A16_UNORM' specifies a four-component, 64-bit unsigned
-- normalized format that has a 16-bit R component in bytes 0..1, a 16-bit
-- G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a
-- 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_UNORM :: Format
$mFORMAT_R16G16B16A16_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_UNORM = Format 91
-- | 'FORMAT_R16G16B16A16_SNORM' specifies a four-component, 64-bit signed
-- normalized format that has a 16-bit R component in bytes 0..1, a 16-bit
-- G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a
-- 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_SNORM :: Format
$mFORMAT_R16G16B16A16_SNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_SNORM = Format 92
-- | 'FORMAT_R16G16B16A16_USCALED' specifies a four-component, 64-bit
-- unsigned scaled integer format that has a 16-bit R component in bytes
-- 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes
-- 4..5, and a 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_USCALED :: Format
$mFORMAT_R16G16B16A16_USCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_USCALED = Format 93
-- | 'FORMAT_R16G16B16A16_SSCALED' specifies a four-component, 64-bit signed
-- scaled integer format that has a 16-bit R component in bytes 0..1, a
-- 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5,
-- and a 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_SSCALED :: Format
$mFORMAT_R16G16B16A16_SSCALED :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_SSCALED = Format 94
-- | 'FORMAT_R16G16B16A16_UINT' specifies a four-component, 64-bit unsigned
-- integer format that has a 16-bit R component in bytes 0..1, a 16-bit G
-- component in bytes 2..3, a 16-bit B component in bytes 4..5, and a
-- 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_UINT :: Format
$mFORMAT_R16G16B16A16_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_UINT = Format 95
-- | 'FORMAT_R16G16B16A16_SINT' specifies a four-component, 64-bit signed
-- integer format that has a 16-bit R component in bytes 0..1, a 16-bit G
-- component in bytes 2..3, a 16-bit B component in bytes 4..5, and a
-- 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_SINT :: Format
$mFORMAT_R16G16B16A16_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_SINT = Format 96
-- | 'FORMAT_R16G16B16A16_SFLOAT' specifies a four-component, 64-bit signed
-- floating-point format that has a 16-bit R component in bytes 0..1, a
-- 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5,
-- and a 16-bit A component in bytes 6..7.
pattern $bFORMAT_R16G16B16A16_SFLOAT :: Format
$mFORMAT_R16G16B16A16_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R16G16B16A16_SFLOAT = Format 97
-- | 'FORMAT_R32_UINT' specifies a one-component, 32-bit unsigned integer
-- format that has a single 32-bit R component.
pattern $bFORMAT_R32_UINT :: Format
$mFORMAT_R32_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32_UINT = Format 98
-- | 'FORMAT_R32_SINT' specifies a one-component, 32-bit signed integer
-- format that has a single 32-bit R component.
pattern $bFORMAT_R32_SINT :: Format
$mFORMAT_R32_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32_SINT = Format 99
-- | 'FORMAT_R32_SFLOAT' specifies a one-component, 32-bit signed
-- floating-point format that has a single 32-bit R component.
pattern $bFORMAT_R32_SFLOAT :: Format
$mFORMAT_R32_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32_SFLOAT = Format 100
-- | 'FORMAT_R32G32_UINT' specifies a two-component, 64-bit unsigned integer
-- format that has a 32-bit R component in bytes 0..3, and a 32-bit G
-- component in bytes 4..7.
pattern $bFORMAT_R32G32_UINT :: Format
$mFORMAT_R32G32_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32_UINT = Format 101
-- | 'FORMAT_R32G32_SINT' specifies a two-component, 64-bit signed integer
-- format that has a 32-bit R component in bytes 0..3, and a 32-bit G
-- component in bytes 4..7.
pattern $bFORMAT_R32G32_SINT :: Format
$mFORMAT_R32G32_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32_SINT = Format 102
-- | 'FORMAT_R32G32_SFLOAT' specifies a two-component, 64-bit signed
-- floating-point format that has a 32-bit R component in bytes 0..3, and a
-- 32-bit G component in bytes 4..7.
pattern $bFORMAT_R32G32_SFLOAT :: Format
$mFORMAT_R32G32_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32_SFLOAT = Format 103
-- | 'FORMAT_R32G32B32_UINT' specifies a three-component, 96-bit unsigned
-- integer format that has a 32-bit R component in bytes 0..3, a 32-bit G
-- component in bytes 4..7, and a 32-bit B component in bytes 8..11.
pattern $bFORMAT_R32G32B32_UINT :: Format
$mFORMAT_R32G32B32_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32_UINT = Format 104
-- | 'FORMAT_R32G32B32_SINT' specifies a three-component, 96-bit signed
-- integer format that has a 32-bit R component in bytes 0..3, a 32-bit G
-- component in bytes 4..7, and a 32-bit B component in bytes 8..11.
pattern $bFORMAT_R32G32B32_SINT :: Format
$mFORMAT_R32G32B32_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32_SINT = Format 105
-- | 'FORMAT_R32G32B32_SFLOAT' specifies a three-component, 96-bit signed
-- floating-point format that has a 32-bit R component in bytes 0..3, a
-- 32-bit G component in bytes 4..7, and a 32-bit B component in bytes
-- 8..11.
pattern $bFORMAT_R32G32B32_SFLOAT :: Format
$mFORMAT_R32G32B32_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32_SFLOAT = Format 106
-- | 'FORMAT_R32G32B32A32_UINT' specifies a four-component, 128-bit unsigned
-- integer format that has a 32-bit R component in bytes 0..3, a 32-bit G
-- component in bytes 4..7, a 32-bit B component in bytes 8..11, and a
-- 32-bit A component in bytes 12..15.
pattern $bFORMAT_R32G32B32A32_UINT :: Format
$mFORMAT_R32G32B32A32_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32A32_UINT = Format 107
-- | 'FORMAT_R32G32B32A32_SINT' specifies a four-component, 128-bit signed
-- integer format that has a 32-bit R component in bytes 0..3, a 32-bit G
-- component in bytes 4..7, a 32-bit B component in bytes 8..11, and a
-- 32-bit A component in bytes 12..15.
pattern $bFORMAT_R32G32B32A32_SINT :: Format
$mFORMAT_R32G32B32A32_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32A32_SINT = Format 108
-- | 'FORMAT_R32G32B32A32_SFLOAT' specifies a four-component, 128-bit signed
-- floating-point format that has a 32-bit R component in bytes 0..3, a
-- 32-bit G component in bytes 4..7, a 32-bit B component in bytes 8..11,
-- and a 32-bit A component in bytes 12..15.
pattern $bFORMAT_R32G32B32A32_SFLOAT :: Format
$mFORMAT_R32G32B32A32_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R32G32B32A32_SFLOAT = Format 109
-- | 'FORMAT_R64_UINT' specifies a one-component, 64-bit unsigned integer
-- format that has a single 64-bit R component.
pattern $bFORMAT_R64_UINT :: Format
$mFORMAT_R64_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64_UINT = Format 110
-- | 'FORMAT_R64_SINT' specifies a one-component, 64-bit signed integer
-- format that has a single 64-bit R component.
pattern $bFORMAT_R64_SINT :: Format
$mFORMAT_R64_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64_SINT = Format 111
-- | 'FORMAT_R64_SFLOAT' specifies a one-component, 64-bit signed
-- floating-point format that has a single 64-bit R component.
pattern $bFORMAT_R64_SFLOAT :: Format
$mFORMAT_R64_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64_SFLOAT = Format 112
-- | 'FORMAT_R64G64_UINT' specifies a two-component, 128-bit unsigned integer
-- format that has a 64-bit R component in bytes 0..7, and a 64-bit G
-- component in bytes 8..15.
pattern $bFORMAT_R64G64_UINT :: Format
$mFORMAT_R64G64_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64_UINT = Format 113
-- | 'FORMAT_R64G64_SINT' specifies a two-component, 128-bit signed integer
-- format that has a 64-bit R component in bytes 0..7, and a 64-bit G
-- component in bytes 8..15.
pattern $bFORMAT_R64G64_SINT :: Format
$mFORMAT_R64G64_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64_SINT = Format 114
-- | 'FORMAT_R64G64_SFLOAT' specifies a two-component, 128-bit signed
-- floating-point format that has a 64-bit R component in bytes 0..7, and a
-- 64-bit G component in bytes 8..15.
pattern $bFORMAT_R64G64_SFLOAT :: Format
$mFORMAT_R64G64_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64_SFLOAT = Format 115
-- | 'FORMAT_R64G64B64_UINT' specifies a three-component, 192-bit unsigned
-- integer format that has a 64-bit R component in bytes 0..7, a 64-bit G
-- component in bytes 8..15, and a 64-bit B component in bytes 16..23.
pattern $bFORMAT_R64G64B64_UINT :: Format
$mFORMAT_R64G64B64_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64_UINT = Format 116
-- | 'FORMAT_R64G64B64_SINT' specifies a three-component, 192-bit signed
-- integer format that has a 64-bit R component in bytes 0..7, a 64-bit G
-- component in bytes 8..15, and a 64-bit B component in bytes 16..23.
pattern $bFORMAT_R64G64B64_SINT :: Format
$mFORMAT_R64G64B64_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64_SINT = Format 117
-- | 'FORMAT_R64G64B64_SFLOAT' specifies a three-component, 192-bit signed
-- floating-point format that has a 64-bit R component in bytes 0..7, a
-- 64-bit G component in bytes 8..15, and a 64-bit B component in bytes
-- 16..23.
pattern $bFORMAT_R64G64B64_SFLOAT :: Format
$mFORMAT_R64G64B64_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64_SFLOAT = Format 118
-- | 'FORMAT_R64G64B64A64_UINT' specifies a four-component, 256-bit unsigned
-- integer format that has a 64-bit R component in bytes 0..7, a 64-bit G
-- component in bytes 8..15, a 64-bit B component in bytes 16..23, and a
-- 64-bit A component in bytes 24..31.
pattern $bFORMAT_R64G64B64A64_UINT :: Format
$mFORMAT_R64G64B64A64_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64A64_UINT = Format 119
-- | 'FORMAT_R64G64B64A64_SINT' specifies a four-component, 256-bit signed
-- integer format that has a 64-bit R component in bytes 0..7, a 64-bit G
-- component in bytes 8..15, a 64-bit B component in bytes 16..23, and a
-- 64-bit A component in bytes 24..31.
pattern $bFORMAT_R64G64B64A64_SINT :: Format
$mFORMAT_R64G64B64A64_SINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64A64_SINT = Format 120
-- | 'FORMAT_R64G64B64A64_SFLOAT' specifies a four-component, 256-bit signed
-- floating-point format that has a 64-bit R component in bytes 0..7, a
-- 64-bit G component in bytes 8..15, a 64-bit B component in bytes 16..23,
-- and a 64-bit A component in bytes 24..31.
pattern $bFORMAT_R64G64B64A64_SFLOAT :: Format
$mFORMAT_R64G64B64A64_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R64G64B64A64_SFLOAT = Format 121
-- | 'FORMAT_B10G11R11_UFLOAT_PACK32' specifies a three-component, 32-bit
-- packed unsigned floating-point format that has a 10-bit B component in
-- bits 22..31, an 11-bit G component in bits 11..21, an 11-bit R component
-- in bits 0..10. See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-fp10>
-- and
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-fp11>.
pattern $bFORMAT_B10G11R11_UFLOAT_PACK32 :: Format
$mFORMAT_B10G11R11_UFLOAT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B10G11R11_UFLOAT_PACK32 = Format 122
-- | 'FORMAT_E5B9G9R9_UFLOAT_PACK32' specifies a three-component, 32-bit
-- packed unsigned floating-point format that has a 5-bit shared exponent
-- in bits 27..31, a 9-bit B component mantissa in bits 18..26, a 9-bit G
-- component mantissa in bits 9..17, and a 9-bit R component mantissa in
-- bits 0..8.
pattern $bFORMAT_E5B9G9R9_UFLOAT_PACK32 :: Format
$mFORMAT_E5B9G9R9_UFLOAT_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_E5B9G9R9_UFLOAT_PACK32 = Format 123
-- | 'FORMAT_D16_UNORM' specifies a one-component, 16-bit unsigned normalized
-- format that has a single 16-bit depth component.
pattern $bFORMAT_D16_UNORM :: Format
$mFORMAT_D16_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_D16_UNORM = Format 124
-- | 'FORMAT_X8_D24_UNORM_PACK32' specifies a two-component, 32-bit format
-- that has 24 unsigned normalized bits in the depth component and,
-- optionally:, 8 bits that are unused.
pattern $bFORMAT_X8_D24_UNORM_PACK32 :: Format
$mFORMAT_X8_D24_UNORM_PACK32 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_X8_D24_UNORM_PACK32 = Format 125
-- | 'FORMAT_D32_SFLOAT' specifies a one-component, 32-bit signed
-- floating-point format that has 32-bits in the depth component.
pattern $bFORMAT_D32_SFLOAT :: Format
$mFORMAT_D32_SFLOAT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_D32_SFLOAT = Format 126
-- | 'FORMAT_S8_UINT' specifies a one-component, 8-bit unsigned integer
-- format that has 8-bits in the stencil component.
pattern $bFORMAT_S8_UINT :: Format
$mFORMAT_S8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_S8_UINT = Format 127
-- | 'FORMAT_D16_UNORM_S8_UINT' specifies a two-component, 24-bit format that
-- has 16 unsigned normalized bits in the depth component and 8 unsigned
-- integer bits in the stencil component.
pattern $bFORMAT_D16_UNORM_S8_UINT :: Format
$mFORMAT_D16_UNORM_S8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_D16_UNORM_S8_UINT = Format 128
-- | 'FORMAT_D24_UNORM_S8_UINT' specifies a two-component, 32-bit packed
-- format that has 8 unsigned integer bits in the stencil component, and 24
-- unsigned normalized bits in the depth component.
pattern $bFORMAT_D24_UNORM_S8_UINT :: Format
$mFORMAT_D24_UNORM_S8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_D24_UNORM_S8_UINT = Format 129
-- | 'FORMAT_D32_SFLOAT_S8_UINT' specifies a two-component format that has 32
-- signed float bits in the depth component and 8 unsigned integer bits in
-- the stencil component. There are optionally: 24-bits that are unused.
pattern $bFORMAT_D32_SFLOAT_S8_UINT :: Format
$mFORMAT_D32_SFLOAT_S8_UINT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_D32_SFLOAT_S8_UINT = Format 130
-- | 'FORMAT_BC1_RGB_UNORM_BLOCK' specifies a three-component,
-- block-compressed format where each 64-bit compressed texel block encodes
-- a 4×4 rectangle of unsigned normalized RGB texel data. This format has
-- no alpha and is considered opaque.
pattern $bFORMAT_BC1_RGB_UNORM_BLOCK :: Format
$mFORMAT_BC1_RGB_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC1_RGB_UNORM_BLOCK = Format 131
-- | 'FORMAT_BC1_RGB_SRGB_BLOCK' specifies a three-component,
-- block-compressed format where each 64-bit compressed texel block encodes
-- a 4×4 rectangle of unsigned normalized RGB texel data with sRGB
-- nonlinear encoding. This format has no alpha and is considered opaque.
pattern $bFORMAT_BC1_RGB_SRGB_BLOCK :: Format
$mFORMAT_BC1_RGB_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC1_RGB_SRGB_BLOCK = Format 132
-- | 'FORMAT_BC1_RGBA_UNORM_BLOCK' specifies a four-component,
-- block-compressed format where each 64-bit compressed texel block encodes
-- a 4×4 rectangle of unsigned normalized RGB texel data, and provides 1
-- bit of alpha.
pattern $bFORMAT_BC1_RGBA_UNORM_BLOCK :: Format
$mFORMAT_BC1_RGBA_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC1_RGBA_UNORM_BLOCK = Format 133
-- | 'FORMAT_BC1_RGBA_SRGB_BLOCK' specifies a four-component,
-- block-compressed format where each 64-bit compressed texel block encodes
-- a 4×4 rectangle of unsigned normalized RGB texel data with sRGB
-- nonlinear encoding, and provides 1 bit of alpha.
pattern $bFORMAT_BC1_RGBA_SRGB_BLOCK :: Format
$mFORMAT_BC1_RGBA_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC1_RGBA_SRGB_BLOCK = Format 134
-- | 'FORMAT_BC2_UNORM_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with the first 64 bits encoding
-- alpha values followed by 64 bits encoding RGB values.
pattern $bFORMAT_BC2_UNORM_BLOCK :: Format
$mFORMAT_BC2_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC2_UNORM_BLOCK = Format 135
-- | 'FORMAT_BC2_SRGB_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with the first 64 bits encoding
-- alpha values followed by 64 bits encoding RGB values with sRGB nonlinear
-- encoding.
pattern $bFORMAT_BC2_SRGB_BLOCK :: Format
$mFORMAT_BC2_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC2_SRGB_BLOCK = Format 136
-- | 'FORMAT_BC3_UNORM_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with the first 64 bits encoding
-- alpha values followed by 64 bits encoding RGB values.
pattern $bFORMAT_BC3_UNORM_BLOCK :: Format
$mFORMAT_BC3_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC3_UNORM_BLOCK = Format 137
-- | 'FORMAT_BC3_SRGB_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with the first 64 bits encoding
-- alpha values followed by 64 bits encoding RGB values with sRGB nonlinear
-- encoding.
pattern $bFORMAT_BC3_SRGB_BLOCK :: Format
$mFORMAT_BC3_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC3_SRGB_BLOCK = Format 138
-- | 'FORMAT_BC4_UNORM_BLOCK' specifies a one-component, block-compressed
-- format where each 64-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized red texel data.
pattern $bFORMAT_BC4_UNORM_BLOCK :: Format
$mFORMAT_BC4_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC4_UNORM_BLOCK = Format 139
-- | 'FORMAT_BC4_SNORM_BLOCK' specifies a one-component, block-compressed
-- format where each 64-bit compressed texel block encodes a 4×4 rectangle
-- of signed normalized red texel data.
pattern $bFORMAT_BC4_SNORM_BLOCK :: Format
$mFORMAT_BC4_SNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC4_SNORM_BLOCK = Format 140
-- | 'FORMAT_BC5_UNORM_BLOCK' specifies a two-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RG texel data with the first 64 bits encoding red
-- values followed by 64 bits encoding green values.
pattern $bFORMAT_BC5_UNORM_BLOCK :: Format
$mFORMAT_BC5_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC5_UNORM_BLOCK = Format 141
-- | 'FORMAT_BC5_SNORM_BLOCK' specifies a two-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of signed normalized RG texel data with the first 64 bits encoding red
-- values followed by 64 bits encoding green values.
pattern $bFORMAT_BC5_SNORM_BLOCK :: Format
$mFORMAT_BC5_SNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC5_SNORM_BLOCK = Format 142
-- | 'FORMAT_BC6H_UFLOAT_BLOCK' specifies a three-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned floating-point RGB texel data.
pattern $bFORMAT_BC6H_UFLOAT_BLOCK :: Format
$mFORMAT_BC6H_UFLOAT_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC6H_UFLOAT_BLOCK = Format 143
-- | 'FORMAT_BC6H_SFLOAT_BLOCK' specifies a three-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of signed floating-point RGB texel data.
pattern $bFORMAT_BC6H_SFLOAT_BLOCK :: Format
$mFORMAT_BC6H_SFLOAT_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC6H_SFLOAT_BLOCK = Format 144
-- | 'FORMAT_BC7_UNORM_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data.
pattern $bFORMAT_BC7_UNORM_BLOCK :: Format
$mFORMAT_BC7_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC7_UNORM_BLOCK = Format 145
-- | 'FORMAT_BC7_SRGB_BLOCK' specifies a four-component, block-compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_BC7_SRGB_BLOCK :: Format
$mFORMAT_BC7_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_BC7_SRGB_BLOCK = Format 146
-- | 'FORMAT_ETC2_R8G8B8_UNORM_BLOCK' specifies a three-component, ETC2
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGB texel data. This format has no
-- alpha and is considered opaque.
pattern $bFORMAT_ETC2_R8G8B8_UNORM_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8_UNORM_BLOCK = Format 147
-- | 'FORMAT_ETC2_R8G8B8_SRGB_BLOCK' specifies a three-component, ETC2
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGB texel data with sRGB nonlinear
-- encoding. This format has no alpha and is considered opaque.
pattern $bFORMAT_ETC2_R8G8B8_SRGB_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8_SRGB_BLOCK = Format 148
-- | 'FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK' specifies a four-component, ETC2
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGB texel data, and provides 1 bit of
-- alpha.
pattern $bFORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK = Format 149
-- | 'FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK' specifies a four-component, ETC2
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGB texel data with sRGB nonlinear
-- encoding, and provides 1 bit of alpha.
pattern $bFORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK = Format 150
-- | 'FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK' specifies a four-component, ETC2
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of unsigned normalized RGBA texel data with the first 64
-- bits encoding alpha values followed by 64 bits encoding RGB values.
pattern $bFORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK = Format 151
-- | 'FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK' specifies a four-component, ETC2
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of unsigned normalized RGBA texel data with the first 64
-- bits encoding alpha values followed by 64 bits encoding RGB values with
-- sRGB nonlinear encoding applied.
pattern $bFORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: Format
$mFORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK = Format 152
-- | 'FORMAT_EAC_R11_UNORM_BLOCK' specifies a one-component, ETC2 compressed
-- format where each 64-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized red texel data.
pattern $bFORMAT_EAC_R11_UNORM_BLOCK :: Format
$mFORMAT_EAC_R11_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_EAC_R11_UNORM_BLOCK = Format 153
-- | 'FORMAT_EAC_R11_SNORM_BLOCK' specifies a one-component, ETC2 compressed
-- format where each 64-bit compressed texel block encodes a 4×4 rectangle
-- of signed normalized red texel data.
pattern $bFORMAT_EAC_R11_SNORM_BLOCK :: Format
$mFORMAT_EAC_R11_SNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_EAC_R11_SNORM_BLOCK = Format 154
-- | 'FORMAT_EAC_R11G11_UNORM_BLOCK' specifies a two-component, ETC2
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of unsigned normalized RG texel data with the first 64
-- bits encoding red values followed by 64 bits encoding green values.
pattern $bFORMAT_EAC_R11G11_UNORM_BLOCK :: Format
$mFORMAT_EAC_R11G11_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_EAC_R11G11_UNORM_BLOCK = Format 155
-- | 'FORMAT_EAC_R11G11_SNORM_BLOCK' specifies a two-component, ETC2
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of signed normalized RG texel data with the first 64 bits
-- encoding red values followed by 64 bits encoding green values.
pattern $bFORMAT_EAC_R11G11_SNORM_BLOCK :: Format
$mFORMAT_EAC_R11G11_SNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_EAC_R11G11_SNORM_BLOCK = Format 156
-- | 'FORMAT_ASTC_4x4_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_4x4_UNORM_BLOCK :: Format
$mFORMAT_ASTC_4x4_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_4x4_UNORM_BLOCK = Format 157
-- | 'FORMAT_ASTC_4x4_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes a 4×4 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_ASTC_4x4_SRGB_BLOCK :: Format
$mFORMAT_ASTC_4x4_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_4x4_SRGB_BLOCK = Format 158
-- | 'FORMAT_ASTC_5x4_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 5×4 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_5x4_UNORM_BLOCK :: Format
$mFORMAT_ASTC_5x4_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x4_UNORM_BLOCK = Format 159
-- | 'FORMAT_ASTC_5x4_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes a 5×4 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_ASTC_5x4_SRGB_BLOCK :: Format
$mFORMAT_ASTC_5x4_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x4_SRGB_BLOCK = Format 160
-- | 'FORMAT_ASTC_5x5_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 5×5 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_5x5_UNORM_BLOCK :: Format
$mFORMAT_ASTC_5x5_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x5_UNORM_BLOCK = Format 161
-- | 'FORMAT_ASTC_5x5_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes a 5×5 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_ASTC_5x5_SRGB_BLOCK :: Format
$mFORMAT_ASTC_5x5_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x5_SRGB_BLOCK = Format 162
-- | 'FORMAT_ASTC_6x5_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 6×5 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_6x5_UNORM_BLOCK :: Format
$mFORMAT_ASTC_6x5_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x5_UNORM_BLOCK = Format 163
-- | 'FORMAT_ASTC_6x5_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes a 6×5 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_ASTC_6x5_SRGB_BLOCK :: Format
$mFORMAT_ASTC_6x5_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x5_SRGB_BLOCK = Format 164
-- | 'FORMAT_ASTC_6x6_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 6×6 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_6x6_UNORM_BLOCK :: Format
$mFORMAT_ASTC_6x6_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x6_UNORM_BLOCK = Format 165
-- | 'FORMAT_ASTC_6x6_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes a 6×6 rectangle
-- of unsigned normalized RGBA texel data with sRGB nonlinear encoding
-- applied to the RGB components.
pattern $bFORMAT_ASTC_6x6_SRGB_BLOCK :: Format
$mFORMAT_ASTC_6x6_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x6_SRGB_BLOCK = Format 166
-- | 'FORMAT_ASTC_8x5_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes an
-- 8×5 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_8x5_UNORM_BLOCK :: Format
$mFORMAT_ASTC_8x5_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x5_UNORM_BLOCK = Format 167
-- | 'FORMAT_ASTC_8x5_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes an 8×5
-- rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_ASTC_8x5_SRGB_BLOCK :: Format
$mFORMAT_ASTC_8x5_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x5_SRGB_BLOCK = Format 168
-- | 'FORMAT_ASTC_8x6_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes an
-- 8×6 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_8x6_UNORM_BLOCK :: Format
$mFORMAT_ASTC_8x6_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x6_UNORM_BLOCK = Format 169
-- | 'FORMAT_ASTC_8x6_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes an 8×6
-- rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_ASTC_8x6_SRGB_BLOCK :: Format
$mFORMAT_ASTC_8x6_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x6_SRGB_BLOCK = Format 170
-- | 'FORMAT_ASTC_8x8_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes an
-- 8×8 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_8x8_UNORM_BLOCK :: Format
$mFORMAT_ASTC_8x8_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x8_UNORM_BLOCK = Format 171
-- | 'FORMAT_ASTC_8x8_SRGB_BLOCK' specifies a four-component, ASTC compressed
-- format where each 128-bit compressed texel block encodes an 8×8
-- rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_ASTC_8x8_SRGB_BLOCK :: Format
$mFORMAT_ASTC_8x8_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x8_SRGB_BLOCK = Format 172
-- | 'FORMAT_ASTC_10x5_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×5 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_10x5_UNORM_BLOCK :: Format
$mFORMAT_ASTC_10x5_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x5_UNORM_BLOCK = Format 173
-- | 'FORMAT_ASTC_10x5_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×5 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_10x5_SRGB_BLOCK :: Format
$mFORMAT_ASTC_10x5_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x5_SRGB_BLOCK = Format 174
-- | 'FORMAT_ASTC_10x6_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×6 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_10x6_UNORM_BLOCK :: Format
$mFORMAT_ASTC_10x6_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x6_UNORM_BLOCK = Format 175
-- | 'FORMAT_ASTC_10x6_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×6 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_10x6_SRGB_BLOCK :: Format
$mFORMAT_ASTC_10x6_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x6_SRGB_BLOCK = Format 176
-- | 'FORMAT_ASTC_10x8_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×8 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_10x8_UNORM_BLOCK :: Format
$mFORMAT_ASTC_10x8_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x8_UNORM_BLOCK = Format 177
-- | 'FORMAT_ASTC_10x8_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×8 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_10x8_SRGB_BLOCK :: Format
$mFORMAT_ASTC_10x8_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x8_SRGB_BLOCK = Format 178
-- | 'FORMAT_ASTC_10x10_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×10 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_10x10_UNORM_BLOCK :: Format
$mFORMAT_ASTC_10x10_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x10_UNORM_BLOCK = Format 179
-- | 'FORMAT_ASTC_10x10_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×10 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_10x10_SRGB_BLOCK :: Format
$mFORMAT_ASTC_10x10_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x10_SRGB_BLOCK = Format 180
-- | 'FORMAT_ASTC_12x10_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×10 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_12x10_UNORM_BLOCK :: Format
$mFORMAT_ASTC_12x10_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x10_UNORM_BLOCK = Format 181
-- | 'FORMAT_ASTC_12x10_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×10 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_12x10_SRGB_BLOCK :: Format
$mFORMAT_ASTC_12x10_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x10_SRGB_BLOCK = Format 182
-- | 'FORMAT_ASTC_12x12_UNORM_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×12 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_ASTC_12x12_UNORM_BLOCK :: Format
$mFORMAT_ASTC_12x12_UNORM_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x12_UNORM_BLOCK = Format 183
-- | 'FORMAT_ASTC_12x12_SRGB_BLOCK' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×12 rectangle of unsigned normalized RGBA texel data with sRGB
-- nonlinear encoding applied to the RGB components.
pattern $bFORMAT_ASTC_12x12_SRGB_BLOCK :: Format
$mFORMAT_ASTC_12x12_SRGB_BLOCK :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x12_SRGB_BLOCK = Format 184
-- | 'FORMAT_A4B4G4R4_UNORM_PACK16_EXT' specifies a four-component, 16-bit
-- packed unsigned normalized format that has a 4-bit A component in bits
-- 12..15, a 4-bit B component in bits 8..11, a 4-bit G component in bits
-- 4..7, and a 4-bit R component in bits 0..3.
pattern $bFORMAT_A4B4G4R4_UNORM_PACK16_EXT :: Format
$mFORMAT_A4B4G4R4_UNORM_PACK16_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A4B4G4R4_UNORM_PACK16_EXT = Format 1000340001
-- | 'FORMAT_A4R4G4B4_UNORM_PACK16_EXT' specifies a four-component, 16-bit
-- packed unsigned normalized format that has a 4-bit A component in bits
-- 12..15, a 4-bit R component in bits 8..11, a 4-bit G component in bits
-- 4..7, and a 4-bit B component in bits 0..3.
pattern $bFORMAT_A4R4G4B4_UNORM_PACK16_EXT :: Format
$mFORMAT_A4R4G4B4_UNORM_PACK16_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_A4R4G4B4_UNORM_PACK16_EXT = Format 1000340000
-- | 'FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×12 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT = Format 1000066013
-- | 'FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 12×10 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT = Format 1000066012
-- | 'FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×10 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT = Format 1000066011
-- | 'FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×8 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT = Format 1000066010
-- | 'FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×6 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT = Format 1000066009
-- | 'FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 10×5 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT = Format 1000066008
-- | 'FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 8×8 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT = Format 1000066007
-- | 'FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 8×6 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT = Format 1000066006
-- | 'FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 8×5 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT = Format 1000066005
-- | 'FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 6×6 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT = Format 1000066004
-- | 'FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 6×5 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT = Format 1000066003
-- | 'FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 5×5 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT = Format 1000066002
-- | 'FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 5×4 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT = Format 1000066001
-- | 'FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT' specifies a four-component, ASTC
-- compressed format where each 128-bit compressed texel block encodes a
-- 4×4 rectangle of signed floating-point RGBA texel data.
pattern $bFORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT :: Format
$mFORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT = Format 1000066000
-- | 'FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG :: Format
$mFORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG = Format 1000054007
-- | 'FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes an
-- 8×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG :: Format
$mFORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG = Format 1000054006
-- | 'FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG :: Format
$mFORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG = Format 1000054005
-- | 'FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes an
-- 8×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear
-- encoding applied to the RGB components.
pattern $bFORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG :: Format
$mFORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG = Format 1000054004
-- | 'FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG :: Format
$mFORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG = Format 1000054003
-- | 'FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes an
-- 8×4 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG :: Format
$mFORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG = Format 1000054002
-- | 'FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes a 4×4
-- rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG :: Format
$mFORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG = Format 1000054001
-- | 'FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG' specifies a four-component, PVRTC
-- compressed format where each 64-bit compressed texel block encodes an
-- 8×4 rectangle of unsigned normalized RGBA texel data.
pattern $bFORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG :: Format
$mFORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG = Format 1000054000
-- | 'FORMAT_G16_B16_R16_3PLANE_444_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has a 16-bit G component in each 16-bit word
-- of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a
-- 16-bit R component in each 16-bit word of plane 2. Each plane has the
-- same dimensions and each R, G and B component contributes to a single
-- texel. The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane.
pattern $bFORMAT_G16_B16_R16_3PLANE_444_UNORM :: Format
$mFORMAT_G16_B16_R16_3PLANE_444_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16_B16_R16_3PLANE_444_UNORM = Format 1000156033
-- | 'FORMAT_G16_B16R16_2PLANE_422_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has a 16-bit G component in each 16-bit word
-- of plane 0, and a two-component, 32-bit BR plane 1 consisting of a
-- 16-bit B component in the word in bytes 0..1, and a 16-bit R component
-- in the word in bytes 2..3. The horizontal dimensions of the BR plane is
-- halved relative to the image dimensions, and each R and B value is
-- shared with the G components for which
-- \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G16_B16R16_2PLANE_422_UNORM :: Format
$mFORMAT_G16_B16R16_2PLANE_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16_B16R16_2PLANE_422_UNORM = Format 1000156032
-- | 'FORMAT_G16_B16_R16_3PLANE_422_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has a 16-bit G component in each 16-bit word
-- of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a
-- 16-bit R component in each 16-bit word of plane 2. The horizontal
-- dimension of the R and B plane is halved relative to the image
-- dimensions, and each R and B value is shared with the G components for
-- which \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G16_B16_R16_3PLANE_422_UNORM :: Format
$mFORMAT_G16_B16_R16_3PLANE_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16_B16_R16_3PLANE_422_UNORM = Format 1000156031
-- | 'FORMAT_G16_B16R16_2PLANE_420_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has a 16-bit G component in each 16-bit word
-- of plane 0, and a two-component, 32-bit BR plane 1 consisting of a
-- 16-bit B component in the word in bytes 0..1, and a 16-bit R component
-- in the word in bytes 2..3. The horizontal and vertical dimensions of the
-- BR plane is halved relative to the image dimensions, and each R and B
-- value is shared with the G components for which
-- \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G16_B16R16_2PLANE_420_UNORM :: Format
$mFORMAT_G16_B16R16_2PLANE_420_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16_B16R16_2PLANE_420_UNORM = Format 1000156030
-- | 'FORMAT_G16_B16_R16_3PLANE_420_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has a 16-bit G component in each 16-bit word
-- of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a
-- 16-bit R component in each 16-bit word of plane 2. The horizontal and
-- vertical dimensions of the R and B planes are halved relative to the
-- image dimensions, and each R and B component is shared with the G
-- components for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G16_B16_R16_3PLANE_420_UNORM :: Format
$mFORMAT_G16_B16_R16_3PLANE_420_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16_B16_R16_3PLANE_420_UNORM = Format 1000156029
-- | 'FORMAT_B16G16R16G16_422_UNORM' specifies a four-component, 64-bit
-- format containing a pair of G components, an R component, and a B
-- component, collectively encoding a 2×1 rectangle of unsigned normalized
-- RGB texel data. One G value is present at each /i/ coordinate, with the
-- B and R values shared across both G values and thus recorded at half the
-- horizontal resolution of the image. This format has a 16-bit B component
-- in the word in bytes 0..1, a 16-bit G component for the even /i/
-- coordinate in the word in bytes 2..3, a 16-bit R component in the word
-- in bytes 4..5, and a 16-bit G component for the odd /i/ coordinate in
-- the word in bytes 6..7. Images in this format /must/ be defined with a
-- width that is a multiple of two. For the purposes of the constraints on
-- copy extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_B16G16R16G16_422_UNORM :: Format
$mFORMAT_B16G16R16G16_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B16G16R16G16_422_UNORM = Format 1000156028
-- | 'FORMAT_G16B16G16R16_422_UNORM' specifies a four-component, 64-bit
-- format containing a pair of G components, an R component, and a B
-- component, collectively encoding a 2×1 rectangle of unsigned normalized
-- RGB texel data. One G value is present at each /i/ coordinate, with the
-- B and R values shared across both G values and thus recorded at half the
-- horizontal resolution of the image. This format has a 16-bit G component
-- for the even /i/ coordinate in the word in bytes 0..1, a 16-bit B
-- component in the word in bytes 2..3, a 16-bit G component for the odd
-- /i/ coordinate in the word in bytes 4..5, and a 16-bit R component in
-- the word in bytes 6..7. Images in this format /must/ be defined with a
-- width that is a multiple of two. For the purposes of the constraints on
-- copy extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_G16B16G16R16_422_UNORM :: Format
$mFORMAT_G16B16G16R16_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G16B16G16R16_422_UNORM = Format 1000156027
-- | 'FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 12-bit G component
-- in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component
-- in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R
-- component in the top 12 bits of each 16-bit word of plane 2, with the
-- bottom 4 bits of each word unused. Each plane has the same dimensions
-- and each R, G and B component contributes to a single texel. The
-- location of each plane when this image is in linear layout can be
-- determined via 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane.
pattern $bFORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 :: Format
$mFORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 = Format 1000156026
-- | 'FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16' specifies an unsigned
-- normalized /multi-planar format/ that has a 12-bit G component in the
-- top 12 bits of each 16-bit word of plane 0, and a two-component, 32-bit
-- BR plane 1 consisting of a 12-bit B component in the top 12 bits of the
-- word in bytes 0..1, and a 12-bit R component in the top 12 bits of the
-- word in bytes 2..3, the bottom 4 bits of each word unused. The
-- horizontal dimensions of the BR plane is halved relative to the image
-- dimensions, and each R and B value is shared with the G components for
-- which \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 :: Format
$mFORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 = Format 1000156025
-- | 'FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 12-bit G component
-- in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component
-- in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R
-- component in the top 12 bits of each 16-bit word of plane 2, with the
-- bottom 4 bits of each word unused. The horizontal dimension of the R and
-- B plane is halved relative to the image dimensions, and each R and B
-- value is shared with the G components for which
-- \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 :: Format
$mFORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 = Format 1000156024
-- | 'FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16' specifies an unsigned
-- normalized /multi-planar format/ that has a 12-bit G component in the
-- top 12 bits of each 16-bit word of plane 0, and a two-component, 32-bit
-- BR plane 1 consisting of a 12-bit B component in the top 12 bits of the
-- word in bytes 0..1, and a 12-bit R component in the top 12 bits of the
-- word in bytes 2..3, the bottom 4 bits of each word unused. The
-- horizontal and vertical dimensions of the BR plane is halved relative to
-- the image dimensions, and each R and B value is shared with the G
-- components for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 :: Format
$mFORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 = Format 1000156023
-- | 'FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 12-bit G component
-- in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component
-- in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R
-- component in the top 12 bits of each 16-bit word of plane 2, with the
-- bottom 4 bits of each word unused. The horizontal and vertical
-- dimensions of the R and B planes are halved relative to the image
-- dimensions, and each R and B component is shared with the G components
-- for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 :: Format
$mFORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 = Format 1000156022
-- | 'FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16' specifies a
-- four-component, 64-bit format containing a pair of G components, an R
-- component, and a B component, collectively encoding a 2×1 rectangle of
-- unsigned normalized RGB texel data. One G value is present at each /i/
-- coordinate, with the B and R values shared across both G values and thus
-- recorded at half the horizontal resolution of the image. This format has
-- a 12-bit B component in the top 12 bits of the word in bytes 0..1, a
-- 12-bit G component for the even /i/ coordinate in the top 12 bits of the
-- word in bytes 2..3, a 12-bit R component in the top 12 bits of the word
-- in bytes 4..5, and a 12-bit G component for the odd /i/ coordinate in
-- the top 12 bits of the word in bytes 6..7, with the bottom 4 bits of
-- each word unused. Images in this format /must/ be defined with a width
-- that is a multiple of two. For the purposes of the constraints on copy
-- extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 :: Format
$mFORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 = Format 1000156021
-- | 'FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16' specifies a
-- four-component, 64-bit format containing a pair of G components, an R
-- component, and a B component, collectively encoding a 2×1 rectangle of
-- unsigned normalized RGB texel data. One G value is present at each /i/
-- coordinate, with the B and R values shared across both G values and thus
-- recorded at half the horizontal resolution of the image. This format has
-- a 12-bit G component for the even /i/ coordinate in the top 12 bits of
-- the word in bytes 0..1, a 12-bit B component in the top 12 bits of the
-- word in bytes 2..3, a 12-bit G component for the odd /i/ coordinate in
-- the top 12 bits of the word in bytes 4..5, and a 12-bit R component in
-- the top 12 bits of the word in bytes 6..7, with the bottom 4 bits of
-- each word unused. Images in this format /must/ be defined with a width
-- that is a multiple of two. For the purposes of the constraints on copy
-- extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 :: Format
$mFORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 = Format 1000156020
-- | 'FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16' specifies a four-component,
-- 64-bit unsigned normalized format that has a 12-bit R component in the
-- top 12 bits of the word in bytes 0..1, a 12-bit G component in the top
-- 12 bits of the word in bytes 2..3, a 12-bit B component in the top 12
-- bits of the word in bytes 4..5, and a 12-bit A component in the top 12
-- bits of the word in bytes 6..7, with the bottom 4 bits of each word
-- unused.
pattern $bFORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 :: Format
$mFORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 = Format 1000156019
-- | 'FORMAT_R12X4G12X4_UNORM_2PACK16' specifies a two-component, 32-bit
-- unsigned normalized format that has a 12-bit R component in the top 12
-- bits of the word in bytes 0..1, and a 12-bit G component in the top 12
-- bits of the word in bytes 2..3, with the bottom 4 bits of each word
-- unused.
pattern $bFORMAT_R12X4G12X4_UNORM_2PACK16 :: Format
$mFORMAT_R12X4G12X4_UNORM_2PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R12X4G12X4_UNORM_2PACK16 = Format 1000156018
-- | 'FORMAT_R12X4_UNORM_PACK16' specifies a one-component, 16-bit unsigned
-- normalized format that has a single 12-bit R component in the top 12
-- bits of a 16-bit word, with the bottom 4 bits unused.
pattern $bFORMAT_R12X4_UNORM_PACK16 :: Format
$mFORMAT_R12X4_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R12X4_UNORM_PACK16 = Format 1000156017
-- | 'FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 10-bit G component
-- in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component
-- in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R
-- component in the top 10 bits of each 16-bit word of plane 2, with the
-- bottom 6 bits of each word unused. Each plane has the same dimensions
-- and each R, G and B component contributes to a single texel. The
-- location of each plane when this image is in linear layout can be
-- determined via 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane.
pattern $bFORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 :: Format
$mFORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 = Format 1000156016
-- | 'FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16' specifies an unsigned
-- normalized /multi-planar format/ that has a 10-bit G component in the
-- top 10 bits of each 16-bit word of plane 0, and a two-component, 32-bit
-- BR plane 1 consisting of a 10-bit B component in the top 10 bits of the
-- word in bytes 0..1, and a 10-bit R component in the top 10 bits of the
-- word in bytes 2..3, the bottom 6 bits of each word unused. The
-- horizontal dimensions of the BR plane is halved relative to the image
-- dimensions, and each R and B value is shared with the G components for
-- which \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 :: Format
$mFORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 = Format 1000156015
-- | 'FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 10-bit G component
-- in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component
-- in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R
-- component in the top 10 bits of each 16-bit word of plane 2, with the
-- bottom 6 bits of each word unused. The horizontal dimension of the R and
-- B plane is halved relative to the image dimensions, and each R and B
-- value is shared with the G components for which
-- \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 :: Format
$mFORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 = Format 1000156014
-- | 'FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16' specifies an unsigned
-- normalized /multi-planar format/ that has a 10-bit G component in the
-- top 10 bits of each 16-bit word of plane 0, and a two-component, 32-bit
-- BR plane 1 consisting of a 10-bit B component in the top 10 bits of the
-- word in bytes 0..1, and a 10-bit R component in the top 10 bits of the
-- word in bytes 2..3, the bottom 6 bits of each word unused. The
-- horizontal and vertical dimensions of the BR plane is halved relative to
-- the image dimensions, and each R and B value is shared with the G
-- components for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 :: Format
$mFORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 = Format 1000156013
-- | 'FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16' specifies an
-- unsigned normalized /multi-planar format/ that has a 10-bit G component
-- in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component
-- in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R
-- component in the top 10 bits of each 16-bit word of plane 2, with the
-- bottom 6 bits of each word unused. The horizontal and vertical
-- dimensions of the R and B planes are halved relative to the image
-- dimensions, and each R and B component is shared with the G components
-- for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 :: Format
$mFORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 = Format 1000156012
-- | 'FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16' specifies a
-- four-component, 64-bit format containing a pair of G components, an R
-- component, and a B component, collectively encoding a 2×1 rectangle of
-- unsigned normalized RGB texel data. One G value is present at each /i/
-- coordinate, with the B and R values shared across both G values and thus
-- recorded at half the horizontal resolution of the image. This format has
-- a 10-bit B component in the top 10 bits of the word in bytes 0..1, a
-- 10-bit G component for the even /i/ coordinate in the top 10 bits of the
-- word in bytes 2..3, a 10-bit R component in the top 10 bits of the word
-- in bytes 4..5, and a 10-bit G component for the odd /i/ coordinate in
-- the top 10 bits of the word in bytes 6..7, with the bottom 6 bits of
-- each word unused. Images in this format /must/ be defined with a width
-- that is a multiple of two. For the purposes of the constraints on copy
-- extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 :: Format
$mFORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 = Format 1000156011
-- | 'FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16' specifies a
-- four-component, 64-bit format containing a pair of G components, an R
-- component, and a B component, collectively encoding a 2×1 rectangle of
-- unsigned normalized RGB texel data. One G value is present at each /i/
-- coordinate, with the B and R values shared across both G values and thus
-- recorded at half the horizontal resolution of the image. This format has
-- a 10-bit G component for the even /i/ coordinate in the top 10 bits of
-- the word in bytes 0..1, a 10-bit B component in the top 10 bits of the
-- word in bytes 2..3, a 10-bit G component for the odd /i/ coordinate in
-- the top 10 bits of the word in bytes 4..5, and a 10-bit R component in
-- the top 10 bits of the word in bytes 6..7, with the bottom 6 bits of
-- each word unused. Images in this format /must/ be defined with a width
-- that is a multiple of two. For the purposes of the constraints on copy
-- extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 :: Format
$mFORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 = Format 1000156010
-- | 'FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16' specifies a four-component,
-- 64-bit unsigned normalized format that has a 10-bit R component in the
-- top 10 bits of the word in bytes 0..1, a 10-bit G component in the top
-- 10 bits of the word in bytes 2..3, a 10-bit B component in the top 10
-- bits of the word in bytes 4..5, and a 10-bit A component in the top 10
-- bits of the word in bytes 6..7, with the bottom 6 bits of each word
-- unused.
pattern $bFORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 :: Format
$mFORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 = Format 1000156009
-- | 'FORMAT_R10X6G10X6_UNORM_2PACK16' specifies a two-component, 32-bit
-- unsigned normalized format that has a 10-bit R component in the top 10
-- bits of the word in bytes 0..1, and a 10-bit G component in the top 10
-- bits of the word in bytes 2..3, with the bottom 6 bits of each word
-- unused.
pattern $bFORMAT_R10X6G10X6_UNORM_2PACK16 :: Format
$mFORMAT_R10X6G10X6_UNORM_2PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R10X6G10X6_UNORM_2PACK16 = Format 1000156008
-- | 'FORMAT_R10X6_UNORM_PACK16' specifies a one-component, 16-bit unsigned
-- normalized format that has a single 10-bit R component in the top 10
-- bits of a 16-bit word, with the bottom 6 bits unused.
pattern $bFORMAT_R10X6_UNORM_PACK16 :: Format
$mFORMAT_R10X6_UNORM_PACK16 :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_R10X6_UNORM_PACK16 = Format 1000156007
-- | 'FORMAT_G8_B8_R8_3PLANE_444_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has an 8-bit G component in plane 0, an 8-bit
-- B component in plane 1, and an 8-bit R component in plane 2. Each plane
-- has the same dimensions and each R, G and B component contributes to a
-- single texel. The location of each plane when this image is in linear
-- layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane.
pattern $bFORMAT_G8_B8_R8_3PLANE_444_UNORM :: Format
$mFORMAT_G8_B8_R8_3PLANE_444_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8_B8_R8_3PLANE_444_UNORM = Format 1000156006
-- | 'FORMAT_G8_B8R8_2PLANE_422_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has an 8-bit G component in plane 0, and a
-- two-component, 16-bit BR plane 1 consisting of an 8-bit B component in
-- byte 0 and an 8-bit R component in byte 1. The horizontal dimensions of
-- the BR plane is halved relative to the image dimensions, and each R and
-- B value is shared with the G components for which
-- \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G8_B8R8_2PLANE_422_UNORM :: Format
$mFORMAT_G8_B8R8_2PLANE_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8_B8R8_2PLANE_422_UNORM = Format 1000156005
-- | 'FORMAT_G8_B8_R8_3PLANE_422_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has an 8-bit G component in plane 0, an 8-bit
-- B component in plane 1, and an 8-bit R component in plane 2. The
-- horizontal dimension of the R and B plane is halved relative to the
-- image dimensions, and each R and B value is shared with the G components
-- for which \(\left\lfloor i_G \times 0.5 \right\rfloor = i_B =
-- i_R\). The location of each plane when this image is in linear layout
-- can be determined via 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- using 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT'
-- for the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width that
-- is a multiple of two.
pattern $bFORMAT_G8_B8_R8_3PLANE_422_UNORM :: Format
$mFORMAT_G8_B8_R8_3PLANE_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8_B8_R8_3PLANE_422_UNORM = Format 1000156004
-- | 'FORMAT_G8_B8R8_2PLANE_420_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has an 8-bit G component in plane 0, and a
-- two-component, 16-bit BR plane 1 consisting of an 8-bit B component in
-- byte 0 and an 8-bit R component in byte 1. The horizontal and vertical
-- dimensions of the BR plane is halved relative to the image dimensions,
-- and each R and B value is shared with the G components for which
-- \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the BR plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G8_B8R8_2PLANE_420_UNORM :: Format
$mFORMAT_G8_B8R8_2PLANE_420_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8_B8R8_2PLANE_420_UNORM = Format 1000156003
-- | 'FORMAT_G8_B8_R8_3PLANE_420_UNORM' specifies an unsigned normalized
-- /multi-planar format/ that has an 8-bit G component in plane 0, an 8-bit
-- B component in plane 1, and an 8-bit R component in plane 2. The
-- horizontal and vertical dimensions of the R and B planes are halved
-- relative to the image dimensions, and each R and B component is shared
-- with the G components for which \(\left\lfloor i_G \times 0.5
-- \right\rfloor = i_B = i_R\) and \(\left\lfloor j_G \times 0.5
-- \right\rfloor = j_B = j_R\). The location of each plane when this image
-- is in linear layout can be determined via
-- 'Vulkan.Core10.Image.getImageSubresourceLayout', using
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' for
-- the G plane,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' for
-- the B plane, and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' for
-- the R plane. Images in this format /must/ be defined with a width and
-- height that is a multiple of two.
pattern $bFORMAT_G8_B8_R8_3PLANE_420_UNORM :: Format
$mFORMAT_G8_B8_R8_3PLANE_420_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8_B8_R8_3PLANE_420_UNORM = Format 1000156002
-- | 'FORMAT_B8G8R8G8_422_UNORM' specifies a four-component, 32-bit format
-- containing a pair of G components, an R component, and a B component,
-- collectively encoding a 2×1 rectangle of unsigned normalized RGB texel
-- data. One G value is present at each /i/ coordinate, with the B and R
-- values shared across both G values and thus recorded at half the
-- horizontal resolution of the image. This format has an 8-bit B component
-- in byte 0, an 8-bit G component for the even /i/ coordinate in byte 1,
-- an 8-bit R component in byte 2, and an 8-bit G component for the odd /i/
-- coordinate in byte 3. Images in this format /must/ be defined with a
-- width that is a multiple of two. For the purposes of the constraints on
-- copy extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_B8G8R8G8_422_UNORM :: Format
$mFORMAT_B8G8R8G8_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_B8G8R8G8_422_UNORM = Format 1000156001
-- | 'FORMAT_G8B8G8R8_422_UNORM' specifies a four-component, 32-bit format
-- containing a pair of G components, an R component, and a B component,
-- collectively encoding a 2×1 rectangle of unsigned normalized RGB texel
-- data. One G value is present at each /i/ coordinate, with the B and R
-- values shared across both G values and thus recorded at half the
-- horizontal resolution of the image. This format has an 8-bit G component
-- for the even /i/ coordinate in byte 0, an 8-bit B component in byte 1,
-- an 8-bit G component for the odd /i/ coordinate in byte 2, and an 8-bit
-- R component in byte 3. Images in this format /must/ be defined with a
-- width that is a multiple of two. For the purposes of the constraints on
-- copy extents, this format is treated as a compressed format with a 2×1
-- compressed texel block.
pattern $bFORMAT_G8B8G8R8_422_UNORM :: Format
$mFORMAT_G8B8G8R8_422_UNORM :: forall r. Format -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_G8B8G8R8_422_UNORM = Format 1000156000
{-# complete FORMAT_UNDEFINED,
             FORMAT_R4G4_UNORM_PACK8,
             FORMAT_R4G4B4A4_UNORM_PACK16,
             FORMAT_B4G4R4A4_UNORM_PACK16,
             FORMAT_R5G6B5_UNORM_PACK16,
             FORMAT_B5G6R5_UNORM_PACK16,
             FORMAT_R5G5B5A1_UNORM_PACK16,
             FORMAT_B5G5R5A1_UNORM_PACK16,
             FORMAT_A1R5G5B5_UNORM_PACK16,
             FORMAT_R8_UNORM,
             FORMAT_R8_SNORM,
             FORMAT_R8_USCALED,
             FORMAT_R8_SSCALED,
             FORMAT_R8_UINT,
             FORMAT_R8_SINT,
             FORMAT_R8_SRGB,
             FORMAT_R8G8_UNORM,
             FORMAT_R8G8_SNORM,
             FORMAT_R8G8_USCALED,
             FORMAT_R8G8_SSCALED,
             FORMAT_R8G8_UINT,
             FORMAT_R8G8_SINT,
             FORMAT_R8G8_SRGB,
             FORMAT_R8G8B8_UNORM,
             FORMAT_R8G8B8_SNORM,
             FORMAT_R8G8B8_USCALED,
             FORMAT_R8G8B8_SSCALED,
             FORMAT_R8G8B8_UINT,
             FORMAT_R8G8B8_SINT,
             FORMAT_R8G8B8_SRGB,
             FORMAT_B8G8R8_UNORM,
             FORMAT_B8G8R8_SNORM,
             FORMAT_B8G8R8_USCALED,
             FORMAT_B8G8R8_SSCALED,
             FORMAT_B8G8R8_UINT,
             FORMAT_B8G8R8_SINT,
             FORMAT_B8G8R8_SRGB,
             FORMAT_R8G8B8A8_UNORM,
             FORMAT_R8G8B8A8_SNORM,
             FORMAT_R8G8B8A8_USCALED,
             FORMAT_R8G8B8A8_SSCALED,
             FORMAT_R8G8B8A8_UINT,
             FORMAT_R8G8B8A8_SINT,
             FORMAT_R8G8B8A8_SRGB,
             FORMAT_B8G8R8A8_UNORM,
             FORMAT_B8G8R8A8_SNORM,
             FORMAT_B8G8R8A8_USCALED,
             FORMAT_B8G8R8A8_SSCALED,
             FORMAT_B8G8R8A8_UINT,
             FORMAT_B8G8R8A8_SINT,
             FORMAT_B8G8R8A8_SRGB,
             FORMAT_A8B8G8R8_UNORM_PACK32,
             FORMAT_A8B8G8R8_SNORM_PACK32,
             FORMAT_A8B8G8R8_USCALED_PACK32,
             FORMAT_A8B8G8R8_SSCALED_PACK32,
             FORMAT_A8B8G8R8_UINT_PACK32,
             FORMAT_A8B8G8R8_SINT_PACK32,
             FORMAT_A8B8G8R8_SRGB_PACK32,
             FORMAT_A2R10G10B10_UNORM_PACK32,
             FORMAT_A2R10G10B10_SNORM_PACK32,
             FORMAT_A2R10G10B10_USCALED_PACK32,
             FORMAT_A2R10G10B10_SSCALED_PACK32,
             FORMAT_A2R10G10B10_UINT_PACK32,
             FORMAT_A2R10G10B10_SINT_PACK32,
             FORMAT_A2B10G10R10_UNORM_PACK32,
             FORMAT_A2B10G10R10_SNORM_PACK32,
             FORMAT_A2B10G10R10_USCALED_PACK32,
             FORMAT_A2B10G10R10_SSCALED_PACK32,
             FORMAT_A2B10G10R10_UINT_PACK32,
             FORMAT_A2B10G10R10_SINT_PACK32,
             FORMAT_R16_UNORM,
             FORMAT_R16_SNORM,
             FORMAT_R16_USCALED,
             FORMAT_R16_SSCALED,
             FORMAT_R16_UINT,
             FORMAT_R16_SINT,
             FORMAT_R16_SFLOAT,
             FORMAT_R16G16_UNORM,
             FORMAT_R16G16_SNORM,
             FORMAT_R16G16_USCALED,
             FORMAT_R16G16_SSCALED,
             FORMAT_R16G16_UINT,
             FORMAT_R16G16_SINT,
             FORMAT_R16G16_SFLOAT,
             FORMAT_R16G16B16_UNORM,
             FORMAT_R16G16B16_SNORM,
             FORMAT_R16G16B16_USCALED,
             FORMAT_R16G16B16_SSCALED,
             FORMAT_R16G16B16_UINT,
             FORMAT_R16G16B16_SINT,
             FORMAT_R16G16B16_SFLOAT,
             FORMAT_R16G16B16A16_UNORM,
             FORMAT_R16G16B16A16_SNORM,
             FORMAT_R16G16B16A16_USCALED,
             FORMAT_R16G16B16A16_SSCALED,
             FORMAT_R16G16B16A16_UINT,
             FORMAT_R16G16B16A16_SINT,
             FORMAT_R16G16B16A16_SFLOAT,
             FORMAT_R32_UINT,
             FORMAT_R32_SINT,
             FORMAT_R32_SFLOAT,
             FORMAT_R32G32_UINT,
             FORMAT_R32G32_SINT,
             FORMAT_R32G32_SFLOAT,
             FORMAT_R32G32B32_UINT,
             FORMAT_R32G32B32_SINT,
             FORMAT_R32G32B32_SFLOAT,
             FORMAT_R32G32B32A32_UINT,
             FORMAT_R32G32B32A32_SINT,
             FORMAT_R32G32B32A32_SFLOAT,
             FORMAT_R64_UINT,
             FORMAT_R64_SINT,
             FORMAT_R64_SFLOAT,
             FORMAT_R64G64_UINT,
             FORMAT_R64G64_SINT,
             FORMAT_R64G64_SFLOAT,
             FORMAT_R64G64B64_UINT,
             FORMAT_R64G64B64_SINT,
             FORMAT_R64G64B64_SFLOAT,
             FORMAT_R64G64B64A64_UINT,
             FORMAT_R64G64B64A64_SINT,
             FORMAT_R64G64B64A64_SFLOAT,
             FORMAT_B10G11R11_UFLOAT_PACK32,
             FORMAT_E5B9G9R9_UFLOAT_PACK32,
             FORMAT_D16_UNORM,
             FORMAT_X8_D24_UNORM_PACK32,
             FORMAT_D32_SFLOAT,
             FORMAT_S8_UINT,
             FORMAT_D16_UNORM_S8_UINT,
             FORMAT_D24_UNORM_S8_UINT,
             FORMAT_D32_SFLOAT_S8_UINT,
             FORMAT_BC1_RGB_UNORM_BLOCK,
             FORMAT_BC1_RGB_SRGB_BLOCK,
             FORMAT_BC1_RGBA_UNORM_BLOCK,
             FORMAT_BC1_RGBA_SRGB_BLOCK,
             FORMAT_BC2_UNORM_BLOCK,
             FORMAT_BC2_SRGB_BLOCK,
             FORMAT_BC3_UNORM_BLOCK,
             FORMAT_BC3_SRGB_BLOCK,
             FORMAT_BC4_UNORM_BLOCK,
             FORMAT_BC4_SNORM_BLOCK,
             FORMAT_BC5_UNORM_BLOCK,
             FORMAT_BC5_SNORM_BLOCK,
             FORMAT_BC6H_UFLOAT_BLOCK,
             FORMAT_BC6H_SFLOAT_BLOCK,
             FORMAT_BC7_UNORM_BLOCK,
             FORMAT_BC7_SRGB_BLOCK,
             FORMAT_ETC2_R8G8B8_UNORM_BLOCK,
             FORMAT_ETC2_R8G8B8_SRGB_BLOCK,
             FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK,
             FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK,
             FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK,
             FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK,
             FORMAT_EAC_R11_UNORM_BLOCK,
             FORMAT_EAC_R11_SNORM_BLOCK,
             FORMAT_EAC_R11G11_UNORM_BLOCK,
             FORMAT_EAC_R11G11_SNORM_BLOCK,
             FORMAT_ASTC_4x4_UNORM_BLOCK,
             FORMAT_ASTC_4x4_SRGB_BLOCK,
             FORMAT_ASTC_5x4_UNORM_BLOCK,
             FORMAT_ASTC_5x4_SRGB_BLOCK,
             FORMAT_ASTC_5x5_UNORM_BLOCK,
             FORMAT_ASTC_5x5_SRGB_BLOCK,
             FORMAT_ASTC_6x5_UNORM_BLOCK,
             FORMAT_ASTC_6x5_SRGB_BLOCK,
             FORMAT_ASTC_6x6_UNORM_BLOCK,
             FORMAT_ASTC_6x6_SRGB_BLOCK,
             FORMAT_ASTC_8x5_UNORM_BLOCK,
             FORMAT_ASTC_8x5_SRGB_BLOCK,
             FORMAT_ASTC_8x6_UNORM_BLOCK,
             FORMAT_ASTC_8x6_SRGB_BLOCK,
             FORMAT_ASTC_8x8_UNORM_BLOCK,
             FORMAT_ASTC_8x8_SRGB_BLOCK,
             FORMAT_ASTC_10x5_UNORM_BLOCK,
             FORMAT_ASTC_10x5_SRGB_BLOCK,
             FORMAT_ASTC_10x6_UNORM_BLOCK,
             FORMAT_ASTC_10x6_SRGB_BLOCK,
             FORMAT_ASTC_10x8_UNORM_BLOCK,
             FORMAT_ASTC_10x8_SRGB_BLOCK,
             FORMAT_ASTC_10x10_UNORM_BLOCK,
             FORMAT_ASTC_10x10_SRGB_BLOCK,
             FORMAT_ASTC_12x10_UNORM_BLOCK,
             FORMAT_ASTC_12x10_SRGB_BLOCK,
             FORMAT_ASTC_12x12_UNORM_BLOCK,
             FORMAT_ASTC_12x12_SRGB_BLOCK,
             FORMAT_A4B4G4R4_UNORM_PACK16_EXT,
             FORMAT_A4R4G4B4_UNORM_PACK16_EXT,
             FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT,
             FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT,
             FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG,
             FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG,
             FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG,
             FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG,
             FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG,
             FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG,
             FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG,
             FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG,
             FORMAT_G16_B16_R16_3PLANE_444_UNORM,
             FORMAT_G16_B16R16_2PLANE_422_UNORM,
             FORMAT_G16_B16_R16_3PLANE_422_UNORM,
             FORMAT_G16_B16R16_2PLANE_420_UNORM,
             FORMAT_G16_B16_R16_3PLANE_420_UNORM,
             FORMAT_B16G16R16G16_422_UNORM,
             FORMAT_G16B16G16R16_422_UNORM,
             FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16,
             FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16,
             FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16,
             FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16,
             FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16,
             FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16,
             FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16,
             FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16,
             FORMAT_R12X4G12X4_UNORM_2PACK16,
             FORMAT_R12X4_UNORM_PACK16,
             FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16,
             FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16,
             FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16,
             FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16,
             FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16,
             FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16,
             FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16,
             FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16,
             FORMAT_R10X6G10X6_UNORM_2PACK16,
             FORMAT_R10X6_UNORM_PACK16,
             FORMAT_G8_B8_R8_3PLANE_444_UNORM,
             FORMAT_G8_B8R8_2PLANE_422_UNORM,
             FORMAT_G8_B8_R8_3PLANE_422_UNORM,
             FORMAT_G8_B8R8_2PLANE_420_UNORM,
             FORMAT_G8_B8_R8_3PLANE_420_UNORM,
             FORMAT_B8G8R8G8_422_UNORM,
             FORMAT_G8B8G8R8_422_UNORM :: Format #-}

instance Show Format where
  showsPrec :: Int -> Format -> ShowS
showsPrec p :: Int
p = \case
    FORMAT_UNDEFINED -> String -> ShowS
showString "FORMAT_UNDEFINED"
    FORMAT_R4G4_UNORM_PACK8 -> String -> ShowS
showString "FORMAT_R4G4_UNORM_PACK8"
    FORMAT_R4G4B4A4_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_R4G4B4A4_UNORM_PACK16"
    FORMAT_B4G4R4A4_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_B4G4R4A4_UNORM_PACK16"
    FORMAT_R5G6B5_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_R5G6B5_UNORM_PACK16"
    FORMAT_B5G6R5_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_B5G6R5_UNORM_PACK16"
    FORMAT_R5G5B5A1_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_R5G5B5A1_UNORM_PACK16"
    FORMAT_B5G5R5A1_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_B5G5R5A1_UNORM_PACK16"
    FORMAT_A1R5G5B5_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_A1R5G5B5_UNORM_PACK16"
    FORMAT_R8_UNORM -> String -> ShowS
showString "FORMAT_R8_UNORM"
    FORMAT_R8_SNORM -> String -> ShowS
showString "FORMAT_R8_SNORM"
    FORMAT_R8_USCALED -> String -> ShowS
showString "FORMAT_R8_USCALED"
    FORMAT_R8_SSCALED -> String -> ShowS
showString "FORMAT_R8_SSCALED"
    FORMAT_R8_UINT -> String -> ShowS
showString "FORMAT_R8_UINT"
    FORMAT_R8_SINT -> String -> ShowS
showString "FORMAT_R8_SINT"
    FORMAT_R8_SRGB -> String -> ShowS
showString "FORMAT_R8_SRGB"
    FORMAT_R8G8_UNORM -> String -> ShowS
showString "FORMAT_R8G8_UNORM"
    FORMAT_R8G8_SNORM -> String -> ShowS
showString "FORMAT_R8G8_SNORM"
    FORMAT_R8G8_USCALED -> String -> ShowS
showString "FORMAT_R8G8_USCALED"
    FORMAT_R8G8_SSCALED -> String -> ShowS
showString "FORMAT_R8G8_SSCALED"
    FORMAT_R8G8_UINT -> String -> ShowS
showString "FORMAT_R8G8_UINT"
    FORMAT_R8G8_SINT -> String -> ShowS
showString "FORMAT_R8G8_SINT"
    FORMAT_R8G8_SRGB -> String -> ShowS
showString "FORMAT_R8G8_SRGB"
    FORMAT_R8G8B8_UNORM -> String -> ShowS
showString "FORMAT_R8G8B8_UNORM"
    FORMAT_R8G8B8_SNORM -> String -> ShowS
showString "FORMAT_R8G8B8_SNORM"
    FORMAT_R8G8B8_USCALED -> String -> ShowS
showString "FORMAT_R8G8B8_USCALED"
    FORMAT_R8G8B8_SSCALED -> String -> ShowS
showString "FORMAT_R8G8B8_SSCALED"
    FORMAT_R8G8B8_UINT -> String -> ShowS
showString "FORMAT_R8G8B8_UINT"
    FORMAT_R8G8B8_SINT -> String -> ShowS
showString "FORMAT_R8G8B8_SINT"
    FORMAT_R8G8B8_SRGB -> String -> ShowS
showString "FORMAT_R8G8B8_SRGB"
    FORMAT_B8G8R8_UNORM -> String -> ShowS
showString "FORMAT_B8G8R8_UNORM"
    FORMAT_B8G8R8_SNORM -> String -> ShowS
showString "FORMAT_B8G8R8_SNORM"
    FORMAT_B8G8R8_USCALED -> String -> ShowS
showString "FORMAT_B8G8R8_USCALED"
    FORMAT_B8G8R8_SSCALED -> String -> ShowS
showString "FORMAT_B8G8R8_SSCALED"
    FORMAT_B8G8R8_UINT -> String -> ShowS
showString "FORMAT_B8G8R8_UINT"
    FORMAT_B8G8R8_SINT -> String -> ShowS
showString "FORMAT_B8G8R8_SINT"
    FORMAT_B8G8R8_SRGB -> String -> ShowS
showString "FORMAT_B8G8R8_SRGB"
    FORMAT_R8G8B8A8_UNORM -> String -> ShowS
showString "FORMAT_R8G8B8A8_UNORM"
    FORMAT_R8G8B8A8_SNORM -> String -> ShowS
showString "FORMAT_R8G8B8A8_SNORM"
    FORMAT_R8G8B8A8_USCALED -> String -> ShowS
showString "FORMAT_R8G8B8A8_USCALED"
    FORMAT_R8G8B8A8_SSCALED -> String -> ShowS
showString "FORMAT_R8G8B8A8_SSCALED"
    FORMAT_R8G8B8A8_UINT -> String -> ShowS
showString "FORMAT_R8G8B8A8_UINT"
    FORMAT_R8G8B8A8_SINT -> String -> ShowS
showString "FORMAT_R8G8B8A8_SINT"
    FORMAT_R8G8B8A8_SRGB -> String -> ShowS
showString "FORMAT_R8G8B8A8_SRGB"
    FORMAT_B8G8R8A8_UNORM -> String -> ShowS
showString "FORMAT_B8G8R8A8_UNORM"
    FORMAT_B8G8R8A8_SNORM -> String -> ShowS
showString "FORMAT_B8G8R8A8_SNORM"
    FORMAT_B8G8R8A8_USCALED -> String -> ShowS
showString "FORMAT_B8G8R8A8_USCALED"
    FORMAT_B8G8R8A8_SSCALED -> String -> ShowS
showString "FORMAT_B8G8R8A8_SSCALED"
    FORMAT_B8G8R8A8_UINT -> String -> ShowS
showString "FORMAT_B8G8R8A8_UINT"
    FORMAT_B8G8R8A8_SINT -> String -> ShowS
showString "FORMAT_B8G8R8A8_SINT"
    FORMAT_B8G8R8A8_SRGB -> String -> ShowS
showString "FORMAT_B8G8R8A8_SRGB"
    FORMAT_A8B8G8R8_UNORM_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_UNORM_PACK32"
    FORMAT_A8B8G8R8_SNORM_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_SNORM_PACK32"
    FORMAT_A8B8G8R8_USCALED_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_USCALED_PACK32"
    FORMAT_A8B8G8R8_SSCALED_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_SSCALED_PACK32"
    FORMAT_A8B8G8R8_UINT_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_UINT_PACK32"
    FORMAT_A8B8G8R8_SINT_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_SINT_PACK32"
    FORMAT_A8B8G8R8_SRGB_PACK32 -> String -> ShowS
showString "FORMAT_A8B8G8R8_SRGB_PACK32"
    FORMAT_A2R10G10B10_UNORM_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_UNORM_PACK32"
    FORMAT_A2R10G10B10_SNORM_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_SNORM_PACK32"
    FORMAT_A2R10G10B10_USCALED_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_USCALED_PACK32"
    FORMAT_A2R10G10B10_SSCALED_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_SSCALED_PACK32"
    FORMAT_A2R10G10B10_UINT_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_UINT_PACK32"
    FORMAT_A2R10G10B10_SINT_PACK32 -> String -> ShowS
showString "FORMAT_A2R10G10B10_SINT_PACK32"
    FORMAT_A2B10G10R10_UNORM_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_UNORM_PACK32"
    FORMAT_A2B10G10R10_SNORM_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_SNORM_PACK32"
    FORMAT_A2B10G10R10_USCALED_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_USCALED_PACK32"
    FORMAT_A2B10G10R10_SSCALED_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_SSCALED_PACK32"
    FORMAT_A2B10G10R10_UINT_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_UINT_PACK32"
    FORMAT_A2B10G10R10_SINT_PACK32 -> String -> ShowS
showString "FORMAT_A2B10G10R10_SINT_PACK32"
    FORMAT_R16_UNORM -> String -> ShowS
showString "FORMAT_R16_UNORM"
    FORMAT_R16_SNORM -> String -> ShowS
showString "FORMAT_R16_SNORM"
    FORMAT_R16_USCALED -> String -> ShowS
showString "FORMAT_R16_USCALED"
    FORMAT_R16_SSCALED -> String -> ShowS
showString "FORMAT_R16_SSCALED"
    FORMAT_R16_UINT -> String -> ShowS
showString "FORMAT_R16_UINT"
    FORMAT_R16_SINT -> String -> ShowS
showString "FORMAT_R16_SINT"
    FORMAT_R16_SFLOAT -> String -> ShowS
showString "FORMAT_R16_SFLOAT"
    FORMAT_R16G16_UNORM -> String -> ShowS
showString "FORMAT_R16G16_UNORM"
    FORMAT_R16G16_SNORM -> String -> ShowS
showString "FORMAT_R16G16_SNORM"
    FORMAT_R16G16_USCALED -> String -> ShowS
showString "FORMAT_R16G16_USCALED"
    FORMAT_R16G16_SSCALED -> String -> ShowS
showString "FORMAT_R16G16_SSCALED"
    FORMAT_R16G16_UINT -> String -> ShowS
showString "FORMAT_R16G16_UINT"
    FORMAT_R16G16_SINT -> String -> ShowS
showString "FORMAT_R16G16_SINT"
    FORMAT_R16G16_SFLOAT -> String -> ShowS
showString "FORMAT_R16G16_SFLOAT"
    FORMAT_R16G16B16_UNORM -> String -> ShowS
showString "FORMAT_R16G16B16_UNORM"
    FORMAT_R16G16B16_SNORM -> String -> ShowS
showString "FORMAT_R16G16B16_SNORM"
    FORMAT_R16G16B16_USCALED -> String -> ShowS
showString "FORMAT_R16G16B16_USCALED"
    FORMAT_R16G16B16_SSCALED -> String -> ShowS
showString "FORMAT_R16G16B16_SSCALED"
    FORMAT_R16G16B16_UINT -> String -> ShowS
showString "FORMAT_R16G16B16_UINT"
    FORMAT_R16G16B16_SINT -> String -> ShowS
showString "FORMAT_R16G16B16_SINT"
    FORMAT_R16G16B16_SFLOAT -> String -> ShowS
showString "FORMAT_R16G16B16_SFLOAT"
    FORMAT_R16G16B16A16_UNORM -> String -> ShowS
showString "FORMAT_R16G16B16A16_UNORM"
    FORMAT_R16G16B16A16_SNORM -> String -> ShowS
showString "FORMAT_R16G16B16A16_SNORM"
    FORMAT_R16G16B16A16_USCALED -> String -> ShowS
showString "FORMAT_R16G16B16A16_USCALED"
    FORMAT_R16G16B16A16_SSCALED -> String -> ShowS
showString "FORMAT_R16G16B16A16_SSCALED"
    FORMAT_R16G16B16A16_UINT -> String -> ShowS
showString "FORMAT_R16G16B16A16_UINT"
    FORMAT_R16G16B16A16_SINT -> String -> ShowS
showString "FORMAT_R16G16B16A16_SINT"
    FORMAT_R16G16B16A16_SFLOAT -> String -> ShowS
showString "FORMAT_R16G16B16A16_SFLOAT"
    FORMAT_R32_UINT -> String -> ShowS
showString "FORMAT_R32_UINT"
    FORMAT_R32_SINT -> String -> ShowS
showString "FORMAT_R32_SINT"
    FORMAT_R32_SFLOAT -> String -> ShowS
showString "FORMAT_R32_SFLOAT"
    FORMAT_R32G32_UINT -> String -> ShowS
showString "FORMAT_R32G32_UINT"
    FORMAT_R32G32_SINT -> String -> ShowS
showString "FORMAT_R32G32_SINT"
    FORMAT_R32G32_SFLOAT -> String -> ShowS
showString "FORMAT_R32G32_SFLOAT"
    FORMAT_R32G32B32_UINT -> String -> ShowS
showString "FORMAT_R32G32B32_UINT"
    FORMAT_R32G32B32_SINT -> String -> ShowS
showString "FORMAT_R32G32B32_SINT"
    FORMAT_R32G32B32_SFLOAT -> String -> ShowS
showString "FORMAT_R32G32B32_SFLOAT"
    FORMAT_R32G32B32A32_UINT -> String -> ShowS
showString "FORMAT_R32G32B32A32_UINT"
    FORMAT_R32G32B32A32_SINT -> String -> ShowS
showString "FORMAT_R32G32B32A32_SINT"
    FORMAT_R32G32B32A32_SFLOAT -> String -> ShowS
showString "FORMAT_R32G32B32A32_SFLOAT"
    FORMAT_R64_UINT -> String -> ShowS
showString "FORMAT_R64_UINT"
    FORMAT_R64_SINT -> String -> ShowS
showString "FORMAT_R64_SINT"
    FORMAT_R64_SFLOAT -> String -> ShowS
showString "FORMAT_R64_SFLOAT"
    FORMAT_R64G64_UINT -> String -> ShowS
showString "FORMAT_R64G64_UINT"
    FORMAT_R64G64_SINT -> String -> ShowS
showString "FORMAT_R64G64_SINT"
    FORMAT_R64G64_SFLOAT -> String -> ShowS
showString "FORMAT_R64G64_SFLOAT"
    FORMAT_R64G64B64_UINT -> String -> ShowS
showString "FORMAT_R64G64B64_UINT"
    FORMAT_R64G64B64_SINT -> String -> ShowS
showString "FORMAT_R64G64B64_SINT"
    FORMAT_R64G64B64_SFLOAT -> String -> ShowS
showString "FORMAT_R64G64B64_SFLOAT"
    FORMAT_R64G64B64A64_UINT -> String -> ShowS
showString "FORMAT_R64G64B64A64_UINT"
    FORMAT_R64G64B64A64_SINT -> String -> ShowS
showString "FORMAT_R64G64B64A64_SINT"
    FORMAT_R64G64B64A64_SFLOAT -> String -> ShowS
showString "FORMAT_R64G64B64A64_SFLOAT"
    FORMAT_B10G11R11_UFLOAT_PACK32 -> String -> ShowS
showString "FORMAT_B10G11R11_UFLOAT_PACK32"
    FORMAT_E5B9G9R9_UFLOAT_PACK32 -> String -> ShowS
showString "FORMAT_E5B9G9R9_UFLOAT_PACK32"
    FORMAT_D16_UNORM -> String -> ShowS
showString "FORMAT_D16_UNORM"
    FORMAT_X8_D24_UNORM_PACK32 -> String -> ShowS
showString "FORMAT_X8_D24_UNORM_PACK32"
    FORMAT_D32_SFLOAT -> String -> ShowS
showString "FORMAT_D32_SFLOAT"
    FORMAT_S8_UINT -> String -> ShowS
showString "FORMAT_S8_UINT"
    FORMAT_D16_UNORM_S8_UINT -> String -> ShowS
showString "FORMAT_D16_UNORM_S8_UINT"
    FORMAT_D24_UNORM_S8_UINT -> String -> ShowS
showString "FORMAT_D24_UNORM_S8_UINT"
    FORMAT_D32_SFLOAT_S8_UINT -> String -> ShowS
showString "FORMAT_D32_SFLOAT_S8_UINT"
    FORMAT_BC1_RGB_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC1_RGB_UNORM_BLOCK"
    FORMAT_BC1_RGB_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_BC1_RGB_SRGB_BLOCK"
    FORMAT_BC1_RGBA_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC1_RGBA_UNORM_BLOCK"
    FORMAT_BC1_RGBA_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_BC1_RGBA_SRGB_BLOCK"
    FORMAT_BC2_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC2_UNORM_BLOCK"
    FORMAT_BC2_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_BC2_SRGB_BLOCK"
    FORMAT_BC3_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC3_UNORM_BLOCK"
    FORMAT_BC3_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_BC3_SRGB_BLOCK"
    FORMAT_BC4_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC4_UNORM_BLOCK"
    FORMAT_BC4_SNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC4_SNORM_BLOCK"
    FORMAT_BC5_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC5_UNORM_BLOCK"
    FORMAT_BC5_SNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC5_SNORM_BLOCK"
    FORMAT_BC6H_UFLOAT_BLOCK -> String -> ShowS
showString "FORMAT_BC6H_UFLOAT_BLOCK"
    FORMAT_BC6H_SFLOAT_BLOCK -> String -> ShowS
showString "FORMAT_BC6H_SFLOAT_BLOCK"
    FORMAT_BC7_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_BC7_UNORM_BLOCK"
    FORMAT_BC7_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_BC7_SRGB_BLOCK"
    FORMAT_ETC2_R8G8B8_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8_UNORM_BLOCK"
    FORMAT_ETC2_R8G8B8_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8_SRGB_BLOCK"
    FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK"
    FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK"
    FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK"
    FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK"
    FORMAT_EAC_R11_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_EAC_R11_UNORM_BLOCK"
    FORMAT_EAC_R11_SNORM_BLOCK -> String -> ShowS
showString "FORMAT_EAC_R11_SNORM_BLOCK"
    FORMAT_EAC_R11G11_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_EAC_R11G11_UNORM_BLOCK"
    FORMAT_EAC_R11G11_SNORM_BLOCK -> String -> ShowS
showString "FORMAT_EAC_R11G11_SNORM_BLOCK"
    FORMAT_ASTC_4x4_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_4x4_UNORM_BLOCK"
    FORMAT_ASTC_4x4_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_4x4_SRGB_BLOCK"
    FORMAT_ASTC_5x4_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_5x4_UNORM_BLOCK"
    FORMAT_ASTC_5x4_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_5x4_SRGB_BLOCK"
    FORMAT_ASTC_5x5_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_5x5_UNORM_BLOCK"
    FORMAT_ASTC_5x5_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_5x5_SRGB_BLOCK"
    FORMAT_ASTC_6x5_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_6x5_UNORM_BLOCK"
    FORMAT_ASTC_6x5_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_6x5_SRGB_BLOCK"
    FORMAT_ASTC_6x6_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_6x6_UNORM_BLOCK"
    FORMAT_ASTC_6x6_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_6x6_SRGB_BLOCK"
    FORMAT_ASTC_8x5_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x5_UNORM_BLOCK"
    FORMAT_ASTC_8x5_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x5_SRGB_BLOCK"
    FORMAT_ASTC_8x6_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x6_UNORM_BLOCK"
    FORMAT_ASTC_8x6_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x6_SRGB_BLOCK"
    FORMAT_ASTC_8x8_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x8_UNORM_BLOCK"
    FORMAT_ASTC_8x8_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_8x8_SRGB_BLOCK"
    FORMAT_ASTC_10x5_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x5_UNORM_BLOCK"
    FORMAT_ASTC_10x5_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x5_SRGB_BLOCK"
    FORMAT_ASTC_10x6_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x6_UNORM_BLOCK"
    FORMAT_ASTC_10x6_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x6_SRGB_BLOCK"
    FORMAT_ASTC_10x8_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x8_UNORM_BLOCK"
    FORMAT_ASTC_10x8_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x8_SRGB_BLOCK"
    FORMAT_ASTC_10x10_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x10_UNORM_BLOCK"
    FORMAT_ASTC_10x10_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_10x10_SRGB_BLOCK"
    FORMAT_ASTC_12x10_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_12x10_UNORM_BLOCK"
    FORMAT_ASTC_12x10_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_12x10_SRGB_BLOCK"
    FORMAT_ASTC_12x12_UNORM_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_12x12_UNORM_BLOCK"
    FORMAT_ASTC_12x12_SRGB_BLOCK -> String -> ShowS
showString "FORMAT_ASTC_12x12_SRGB_BLOCK"
    FORMAT_A4B4G4R4_UNORM_PACK16_EXT -> String -> ShowS
showString "FORMAT_A4B4G4R4_UNORM_PACK16_EXT"
    FORMAT_A4R4G4B4_UNORM_PACK16_EXT -> String -> ShowS
showString "FORMAT_A4R4G4B4_UNORM_PACK16_EXT"
    FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT"
    FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT -> String -> ShowS
showString "FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT"
    FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG"
    FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG"
    FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG"
    FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG"
    FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG"
    FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG"
    FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG"
    FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG -> String -> ShowS
showString "FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG"
    FORMAT_G16_B16_R16_3PLANE_444_UNORM -> String -> ShowS
showString "FORMAT_G16_B16_R16_3PLANE_444_UNORM"
    FORMAT_G16_B16R16_2PLANE_422_UNORM -> String -> ShowS
showString "FORMAT_G16_B16R16_2PLANE_422_UNORM"
    FORMAT_G16_B16_R16_3PLANE_422_UNORM -> String -> ShowS
showString "FORMAT_G16_B16_R16_3PLANE_422_UNORM"
    FORMAT_G16_B16R16_2PLANE_420_UNORM -> String -> ShowS
showString "FORMAT_G16_B16R16_2PLANE_420_UNORM"
    FORMAT_G16_B16_R16_3PLANE_420_UNORM -> String -> ShowS
showString "FORMAT_G16_B16_R16_3PLANE_420_UNORM"
    FORMAT_B16G16R16G16_422_UNORM -> String -> ShowS
showString "FORMAT_B16G16R16G16_422_UNORM"
    FORMAT_G16B16G16R16_422_UNORM -> String -> ShowS
showString "FORMAT_G16B16G16R16_422_UNORM"
    FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16"
    FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16"
    FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16"
    FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16"
    FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16"
    FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16"
    FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16"
    FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16"
    FORMAT_R12X4G12X4_UNORM_2PACK16 -> String -> ShowS
showString "FORMAT_R12X4G12X4_UNORM_2PACK16"
    FORMAT_R12X4_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_R12X4_UNORM_PACK16"
    FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16"
    FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16"
    FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16"
    FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16"
    FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 -> String -> ShowS
showString "FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16"
    FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16"
    FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16"
    FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 -> String -> ShowS
showString "FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16"
    FORMAT_R10X6G10X6_UNORM_2PACK16 -> String -> ShowS
showString "FORMAT_R10X6G10X6_UNORM_2PACK16"
    FORMAT_R10X6_UNORM_PACK16 -> String -> ShowS
showString "FORMAT_R10X6_UNORM_PACK16"
    FORMAT_G8_B8_R8_3PLANE_444_UNORM -> String -> ShowS
showString "FORMAT_G8_B8_R8_3PLANE_444_UNORM"
    FORMAT_G8_B8R8_2PLANE_422_UNORM -> String -> ShowS
showString "FORMAT_G8_B8R8_2PLANE_422_UNORM"
    FORMAT_G8_B8_R8_3PLANE_422_UNORM -> String -> ShowS
showString "FORMAT_G8_B8_R8_3PLANE_422_UNORM"
    FORMAT_G8_B8R8_2PLANE_420_UNORM -> String -> ShowS
showString "FORMAT_G8_B8R8_2PLANE_420_UNORM"
    FORMAT_G8_B8_R8_3PLANE_420_UNORM -> String -> ShowS
showString "FORMAT_G8_B8_R8_3PLANE_420_UNORM"
    FORMAT_B8G8R8G8_422_UNORM -> String -> ShowS
showString "FORMAT_B8G8R8G8_422_UNORM"
    FORMAT_G8B8G8R8_422_UNORM -> String -> ShowS
showString "FORMAT_G8B8G8R8_422_UNORM"
    Format x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Format " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read Format where
  readPrec :: ReadPrec Format
readPrec = ReadPrec Format -> ReadPrec Format
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec Format)] -> ReadPrec Format
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("FORMAT_UNDEFINED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_UNDEFINED)
                            , ("FORMAT_R4G4_UNORM_PACK8", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R4G4_UNORM_PACK8)
                            , ("FORMAT_R4G4B4A4_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R4G4B4A4_UNORM_PACK16)
                            , ("FORMAT_B4G4R4A4_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B4G4R4A4_UNORM_PACK16)
                            , ("FORMAT_R5G6B5_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R5G6B5_UNORM_PACK16)
                            , ("FORMAT_B5G6R5_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B5G6R5_UNORM_PACK16)
                            , ("FORMAT_R5G5B5A1_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R5G5B5A1_UNORM_PACK16)
                            , ("FORMAT_B5G5R5A1_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B5G5R5A1_UNORM_PACK16)
                            , ("FORMAT_A1R5G5B5_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A1R5G5B5_UNORM_PACK16)
                            , ("FORMAT_R8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_UNORM)
                            , ("FORMAT_R8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_SNORM)
                            , ("FORMAT_R8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_USCALED)
                            , ("FORMAT_R8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_SSCALED)
                            , ("FORMAT_R8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_UINT)
                            , ("FORMAT_R8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_SINT)
                            , ("FORMAT_R8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8_SRGB)
                            , ("FORMAT_R8G8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_UNORM)
                            , ("FORMAT_R8G8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_SNORM)
                            , ("FORMAT_R8G8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_USCALED)
                            , ("FORMAT_R8G8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_SSCALED)
                            , ("FORMAT_R8G8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_UINT)
                            , ("FORMAT_R8G8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_SINT)
                            , ("FORMAT_R8G8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8_SRGB)
                            , ("FORMAT_R8G8B8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_UNORM)
                            , ("FORMAT_R8G8B8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_SNORM)
                            , ("FORMAT_R8G8B8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_USCALED)
                            , ("FORMAT_R8G8B8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_SSCALED)
                            , ("FORMAT_R8G8B8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_UINT)
                            , ("FORMAT_R8G8B8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_SINT)
                            , ("FORMAT_R8G8B8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8_SRGB)
                            , ("FORMAT_B8G8R8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_UNORM)
                            , ("FORMAT_B8G8R8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_SNORM)
                            , ("FORMAT_B8G8R8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_USCALED)
                            , ("FORMAT_B8G8R8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_SSCALED)
                            , ("FORMAT_B8G8R8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_UINT)
                            , ("FORMAT_B8G8R8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_SINT)
                            , ("FORMAT_B8G8R8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8_SRGB)
                            , ("FORMAT_R8G8B8A8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_UNORM)
                            , ("FORMAT_R8G8B8A8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_SNORM)
                            , ("FORMAT_R8G8B8A8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_USCALED)
                            , ("FORMAT_R8G8B8A8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_SSCALED)
                            , ("FORMAT_R8G8B8A8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_UINT)
                            , ("FORMAT_R8G8B8A8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_SINT)
                            , ("FORMAT_R8G8B8A8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R8G8B8A8_SRGB)
                            , ("FORMAT_B8G8R8A8_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_UNORM)
                            , ("FORMAT_B8G8R8A8_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_SNORM)
                            , ("FORMAT_B8G8R8A8_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_USCALED)
                            , ("FORMAT_B8G8R8A8_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_SSCALED)
                            , ("FORMAT_B8G8R8A8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_UINT)
                            , ("FORMAT_B8G8R8A8_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_SINT)
                            , ("FORMAT_B8G8R8A8_SRGB", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8A8_SRGB)
                            , ("FORMAT_A8B8G8R8_UNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_UNORM_PACK32)
                            , ("FORMAT_A8B8G8R8_SNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_SNORM_PACK32)
                            , ("FORMAT_A8B8G8R8_USCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_USCALED_PACK32)
                            , ("FORMAT_A8B8G8R8_SSCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_SSCALED_PACK32)
                            , ("FORMAT_A8B8G8R8_UINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_UINT_PACK32)
                            , ("FORMAT_A8B8G8R8_SINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_SINT_PACK32)
                            , ("FORMAT_A8B8G8R8_SRGB_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A8B8G8R8_SRGB_PACK32)
                            , ("FORMAT_A2R10G10B10_UNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_UNORM_PACK32)
                            , ("FORMAT_A2R10G10B10_SNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_SNORM_PACK32)
                            , ("FORMAT_A2R10G10B10_USCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_USCALED_PACK32)
                            , ("FORMAT_A2R10G10B10_SSCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_SSCALED_PACK32)
                            , ("FORMAT_A2R10G10B10_UINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_UINT_PACK32)
                            , ("FORMAT_A2R10G10B10_SINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2R10G10B10_SINT_PACK32)
                            , ("FORMAT_A2B10G10R10_UNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_UNORM_PACK32)
                            , ("FORMAT_A2B10G10R10_SNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_SNORM_PACK32)
                            , ("FORMAT_A2B10G10R10_USCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_USCALED_PACK32)
                            , ("FORMAT_A2B10G10R10_SSCALED_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_SSCALED_PACK32)
                            , ("FORMAT_A2B10G10R10_UINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_UINT_PACK32)
                            , ("FORMAT_A2B10G10R10_SINT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A2B10G10R10_SINT_PACK32)
                            , ("FORMAT_R16_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_UNORM)
                            , ("FORMAT_R16_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_SNORM)
                            , ("FORMAT_R16_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_USCALED)
                            , ("FORMAT_R16_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_SSCALED)
                            , ("FORMAT_R16_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_UINT)
                            , ("FORMAT_R16_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_SINT)
                            , ("FORMAT_R16_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16_SFLOAT)
                            , ("FORMAT_R16G16_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_UNORM)
                            , ("FORMAT_R16G16_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_SNORM)
                            , ("FORMAT_R16G16_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_USCALED)
                            , ("FORMAT_R16G16_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_SSCALED)
                            , ("FORMAT_R16G16_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_UINT)
                            , ("FORMAT_R16G16_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_SINT)
                            , ("FORMAT_R16G16_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16_SFLOAT)
                            , ("FORMAT_R16G16B16_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_UNORM)
                            , ("FORMAT_R16G16B16_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_SNORM)
                            , ("FORMAT_R16G16B16_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_USCALED)
                            , ("FORMAT_R16G16B16_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_SSCALED)
                            , ("FORMAT_R16G16B16_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_UINT)
                            , ("FORMAT_R16G16B16_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_SINT)
                            , ("FORMAT_R16G16B16_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16_SFLOAT)
                            , ("FORMAT_R16G16B16A16_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_UNORM)
                            , ("FORMAT_R16G16B16A16_SNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_SNORM)
                            , ("FORMAT_R16G16B16A16_USCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_USCALED)
                            , ("FORMAT_R16G16B16A16_SSCALED", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_SSCALED)
                            , ("FORMAT_R16G16B16A16_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_UINT)
                            , ("FORMAT_R16G16B16A16_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_SINT)
                            , ("FORMAT_R16G16B16A16_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R16G16B16A16_SFLOAT)
                            , ("FORMAT_R32_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32_UINT)
                            , ("FORMAT_R32_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32_SINT)
                            , ("FORMAT_R32_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32_SFLOAT)
                            , ("FORMAT_R32G32_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32_UINT)
                            , ("FORMAT_R32G32_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32_SINT)
                            , ("FORMAT_R32G32_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32_SFLOAT)
                            , ("FORMAT_R32G32B32_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32_UINT)
                            , ("FORMAT_R32G32B32_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32_SINT)
                            , ("FORMAT_R32G32B32_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32_SFLOAT)
                            , ("FORMAT_R32G32B32A32_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32A32_UINT)
                            , ("FORMAT_R32G32B32A32_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32A32_SINT)
                            , ("FORMAT_R32G32B32A32_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R32G32B32A32_SFLOAT)
                            , ("FORMAT_R64_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64_UINT)
                            , ("FORMAT_R64_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64_SINT)
                            , ("FORMAT_R64_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64_SFLOAT)
                            , ("FORMAT_R64G64_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64_UINT)
                            , ("FORMAT_R64G64_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64_SINT)
                            , ("FORMAT_R64G64_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64_SFLOAT)
                            , ("FORMAT_R64G64B64_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64_UINT)
                            , ("FORMAT_R64G64B64_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64_SINT)
                            , ("FORMAT_R64G64B64_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64_SFLOAT)
                            , ("FORMAT_R64G64B64A64_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64A64_UINT)
                            , ("FORMAT_R64G64B64A64_SINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64A64_SINT)
                            , ("FORMAT_R64G64B64A64_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R64G64B64A64_SFLOAT)
                            , ("FORMAT_B10G11R11_UFLOAT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B10G11R11_UFLOAT_PACK32)
                            , ("FORMAT_E5B9G9R9_UFLOAT_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_E5B9G9R9_UFLOAT_PACK32)
                            , ("FORMAT_D16_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_D16_UNORM)
                            , ("FORMAT_X8_D24_UNORM_PACK32", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_X8_D24_UNORM_PACK32)
                            , ("FORMAT_D32_SFLOAT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_D32_SFLOAT)
                            , ("FORMAT_S8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_S8_UINT)
                            , ("FORMAT_D16_UNORM_S8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_D16_UNORM_S8_UINT)
                            , ("FORMAT_D24_UNORM_S8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_D24_UNORM_S8_UINT)
                            , ("FORMAT_D32_SFLOAT_S8_UINT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_D32_SFLOAT_S8_UINT)
                            , ("FORMAT_BC1_RGB_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC1_RGB_UNORM_BLOCK)
                            , ("FORMAT_BC1_RGB_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC1_RGB_SRGB_BLOCK)
                            , ("FORMAT_BC1_RGBA_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC1_RGBA_UNORM_BLOCK)
                            , ("FORMAT_BC1_RGBA_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC1_RGBA_SRGB_BLOCK)
                            , ("FORMAT_BC2_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC2_UNORM_BLOCK)
                            , ("FORMAT_BC2_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC2_SRGB_BLOCK)
                            , ("FORMAT_BC3_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC3_UNORM_BLOCK)
                            , ("FORMAT_BC3_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC3_SRGB_BLOCK)
                            , ("FORMAT_BC4_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC4_UNORM_BLOCK)
                            , ("FORMAT_BC4_SNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC4_SNORM_BLOCK)
                            , ("FORMAT_BC5_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC5_UNORM_BLOCK)
                            , ("FORMAT_BC5_SNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC5_SNORM_BLOCK)
                            , ("FORMAT_BC6H_UFLOAT_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC6H_UFLOAT_BLOCK)
                            , ("FORMAT_BC6H_SFLOAT_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC6H_SFLOAT_BLOCK)
                            , ("FORMAT_BC7_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC7_UNORM_BLOCK)
                            , ("FORMAT_BC7_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_BC7_SRGB_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8_UNORM_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8_SRGB_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK)
                            , ("FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK)
                            , ("FORMAT_EAC_R11_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_EAC_R11_UNORM_BLOCK)
                            , ("FORMAT_EAC_R11_SNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_EAC_R11_SNORM_BLOCK)
                            , ("FORMAT_EAC_R11G11_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_EAC_R11G11_UNORM_BLOCK)
                            , ("FORMAT_EAC_R11G11_SNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_EAC_R11G11_SNORM_BLOCK)
                            , ("FORMAT_ASTC_4x4_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_4x4_UNORM_BLOCK)
                            , ("FORMAT_ASTC_4x4_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_4x4_SRGB_BLOCK)
                            , ("FORMAT_ASTC_5x4_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x4_UNORM_BLOCK)
                            , ("FORMAT_ASTC_5x4_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x4_SRGB_BLOCK)
                            , ("FORMAT_ASTC_5x5_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x5_UNORM_BLOCK)
                            , ("FORMAT_ASTC_5x5_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x5_SRGB_BLOCK)
                            , ("FORMAT_ASTC_6x5_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x5_UNORM_BLOCK)
                            , ("FORMAT_ASTC_6x5_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x5_SRGB_BLOCK)
                            , ("FORMAT_ASTC_6x6_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x6_UNORM_BLOCK)
                            , ("FORMAT_ASTC_6x6_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x6_SRGB_BLOCK)
                            , ("FORMAT_ASTC_8x5_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x5_UNORM_BLOCK)
                            , ("FORMAT_ASTC_8x5_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x5_SRGB_BLOCK)
                            , ("FORMAT_ASTC_8x6_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x6_UNORM_BLOCK)
                            , ("FORMAT_ASTC_8x6_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x6_SRGB_BLOCK)
                            , ("FORMAT_ASTC_8x8_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x8_UNORM_BLOCK)
                            , ("FORMAT_ASTC_8x8_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x8_SRGB_BLOCK)
                            , ("FORMAT_ASTC_10x5_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x5_UNORM_BLOCK)
                            , ("FORMAT_ASTC_10x5_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x5_SRGB_BLOCK)
                            , ("FORMAT_ASTC_10x6_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x6_UNORM_BLOCK)
                            , ("FORMAT_ASTC_10x6_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x6_SRGB_BLOCK)
                            , ("FORMAT_ASTC_10x8_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x8_UNORM_BLOCK)
                            , ("FORMAT_ASTC_10x8_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x8_SRGB_BLOCK)
                            , ("FORMAT_ASTC_10x10_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x10_UNORM_BLOCK)
                            , ("FORMAT_ASTC_10x10_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x10_SRGB_BLOCK)
                            , ("FORMAT_ASTC_12x10_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x10_UNORM_BLOCK)
                            , ("FORMAT_ASTC_12x10_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x10_SRGB_BLOCK)
                            , ("FORMAT_ASTC_12x12_UNORM_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x12_UNORM_BLOCK)
                            , ("FORMAT_ASTC_12x12_SRGB_BLOCK", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x12_SRGB_BLOCK)
                            , ("FORMAT_A4B4G4R4_UNORM_PACK16_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A4B4G4R4_UNORM_PACK16_EXT)
                            , ("FORMAT_A4R4G4B4_UNORM_PACK16_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_A4R4G4B4_UNORM_PACK16_EXT)
                            , ("FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT)
                            , ("FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG)
                            , ("FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG)
                            , ("FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG)
                            , ("FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG)
                            , ("FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG)
                            , ("FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG)
                            , ("FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG)
                            , ("FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG)
                            , ("FORMAT_G16_B16_R16_3PLANE_444_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16_B16_R16_3PLANE_444_UNORM)
                            , ("FORMAT_G16_B16R16_2PLANE_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16_B16R16_2PLANE_422_UNORM)
                            , ("FORMAT_G16_B16_R16_3PLANE_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16_B16_R16_3PLANE_422_UNORM)
                            , ("FORMAT_G16_B16R16_2PLANE_420_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16_B16R16_2PLANE_420_UNORM)
                            , ("FORMAT_G16_B16_R16_3PLANE_420_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16_B16_R16_3PLANE_420_UNORM)
                            , ("FORMAT_B16G16R16G16_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B16G16R16G16_422_UNORM)
                            , ("FORMAT_G16B16G16R16_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G16B16G16R16_422_UNORM)
                            , ("FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16)
                            , ("FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16)
                            , ("FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16)
                            , ("FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16)
                            , ("FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16)
                            , ("FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16)
                            , ("FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16)
                            , ("FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16)
                            , ("FORMAT_R12X4G12X4_UNORM_2PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R12X4G12X4_UNORM_2PACK16)
                            , ("FORMAT_R12X4_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R12X4_UNORM_PACK16)
                            , ("FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16)
                            , ("FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16)
                            , ("FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16)
                            , ("FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16)
                            , ("FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16)
                            , ("FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16)
                            , ("FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16)
                            , ("FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16)
                            , ("FORMAT_R10X6G10X6_UNORM_2PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R10X6G10X6_UNORM_2PACK16)
                            , ("FORMAT_R10X6_UNORM_PACK16", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_R10X6_UNORM_PACK16)
                            , ("FORMAT_G8_B8_R8_3PLANE_444_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8_B8_R8_3PLANE_444_UNORM)
                            , ("FORMAT_G8_B8R8_2PLANE_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8_B8R8_2PLANE_422_UNORM)
                            , ("FORMAT_G8_B8_R8_3PLANE_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8_B8_R8_3PLANE_422_UNORM)
                            , ("FORMAT_G8_B8R8_2PLANE_420_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8_B8R8_2PLANE_420_UNORM)
                            , ("FORMAT_G8_B8_R8_3PLANE_420_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8_B8_R8_3PLANE_420_UNORM)
                            , ("FORMAT_B8G8R8G8_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_B8G8R8G8_422_UNORM)
                            , ("FORMAT_G8B8G8R8_422_UNORM", Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
FORMAT_G8B8G8R8_422_UNORM)]
                     ReadPrec Format -> ReadPrec Format -> ReadPrec Format
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec Format -> ReadPrec Format
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "Format")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       Format -> ReadPrec Format
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> Format
Format Int32
v)))