module Data.SpirV.Reflect.Enums.UserType where import Data.SpirV.Reflect.Enums.Common newtype UserType = UserType Int deriving newtype (UserType -> UserType -> Bool (UserType -> UserType -> Bool) -> (UserType -> UserType -> Bool) -> Eq UserType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: UserType -> UserType -> Bool == :: UserType -> UserType -> Bool $c/= :: UserType -> UserType -> Bool /= :: UserType -> UserType -> Bool Eq, Eq UserType Eq UserType => (UserType -> UserType -> Ordering) -> (UserType -> UserType -> Bool) -> (UserType -> UserType -> Bool) -> (UserType -> UserType -> Bool) -> (UserType -> UserType -> Bool) -> (UserType -> UserType -> UserType) -> (UserType -> UserType -> UserType) -> Ord UserType UserType -> UserType -> Bool UserType -> UserType -> Ordering UserType -> UserType -> UserType 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 $ccompare :: UserType -> UserType -> Ordering compare :: UserType -> UserType -> Ordering $c< :: UserType -> UserType -> Bool < :: UserType -> UserType -> Bool $c<= :: UserType -> UserType -> Bool <= :: UserType -> UserType -> Bool $c> :: UserType -> UserType -> Bool > :: UserType -> UserType -> Bool $c>= :: UserType -> UserType -> Bool >= :: UserType -> UserType -> Bool $cmax :: UserType -> UserType -> UserType max :: UserType -> UserType -> UserType $cmin :: UserType -> UserType -> UserType min :: UserType -> UserType -> UserType Ord, Int -> UserType -> ShowS [UserType] -> ShowS UserType -> String (Int -> UserType -> ShowS) -> (UserType -> String) -> ([UserType] -> ShowS) -> Show UserType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> UserType -> ShowS showsPrec :: Int -> UserType -> ShowS $cshow :: UserType -> String show :: UserType -> String $cshowList :: [UserType] -> ShowS showList :: [UserType] -> ShowS Show, Int -> UserType UserType -> Int UserType -> [UserType] UserType -> UserType UserType -> UserType -> [UserType] UserType -> UserType -> UserType -> [UserType] (UserType -> UserType) -> (UserType -> UserType) -> (Int -> UserType) -> (UserType -> Int) -> (UserType -> [UserType]) -> (UserType -> UserType -> [UserType]) -> (UserType -> UserType -> [UserType]) -> (UserType -> UserType -> UserType -> [UserType]) -> Enum UserType forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a $csucc :: UserType -> UserType succ :: UserType -> UserType $cpred :: UserType -> UserType pred :: UserType -> UserType $ctoEnum :: Int -> UserType toEnum :: Int -> UserType $cfromEnum :: UserType -> Int fromEnum :: UserType -> Int $cenumFrom :: UserType -> [UserType] enumFrom :: UserType -> [UserType] $cenumFromThen :: UserType -> UserType -> [UserType] enumFromThen :: UserType -> UserType -> [UserType] $cenumFromTo :: UserType -> UserType -> [UserType] enumFromTo :: UserType -> UserType -> [UserType] $cenumFromThenTo :: UserType -> UserType -> UserType -> [UserType] enumFromThenTo :: UserType -> UserType -> UserType -> [UserType] Enum) pattern USER_TYPE_INVALID :: UserType pattern $mUSER_TYPE_INVALID :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_INVALID :: UserType USER_TYPE_INVALID = UserType 0 pattern USER_TYPE_CBUFFER :: UserType pattern $mUSER_TYPE_CBUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_CBUFFER :: UserType USER_TYPE_CBUFFER = UserType 1 pattern USER_TYPE_TBUFFER :: UserType pattern $mUSER_TYPE_TBUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TBUFFER :: UserType USER_TYPE_TBUFFER = UserType 2 pattern USER_TYPE_APPEND_STRUCTURED_BUFFER :: UserType pattern $mUSER_TYPE_APPEND_STRUCTURED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_APPEND_STRUCTURED_BUFFER :: UserType USER_TYPE_APPEND_STRUCTURED_BUFFER = UserType 3 pattern USER_TYPE_BUFFER :: UserType pattern $mUSER_TYPE_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_BUFFER :: UserType USER_TYPE_BUFFER = UserType 4 pattern USER_TYPE_BYTE_ADDRESS_BUFFER :: UserType pattern $mUSER_TYPE_BYTE_ADDRESS_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_BYTE_ADDRESS_BUFFER :: UserType USER_TYPE_BYTE_ADDRESS_BUFFER = UserType 5 pattern USER_TYPE_CONSTANT_BUFFER :: UserType pattern $mUSER_TYPE_CONSTANT_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_CONSTANT_BUFFER :: UserType USER_TYPE_CONSTANT_BUFFER = UserType 6 pattern USER_TYPE_CONSUME_STRUCTURED_BUFFER :: UserType pattern $mUSER_TYPE_CONSUME_STRUCTURED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_CONSUME_STRUCTURED_BUFFER :: UserType USER_TYPE_CONSUME_STRUCTURED_BUFFER = UserType 7 pattern USER_TYPE_INPUT_PATCH :: UserType pattern $mUSER_TYPE_INPUT_PATCH :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_INPUT_PATCH :: UserType USER_TYPE_INPUT_PATCH = UserType 8 pattern USER_TYPE_OUTPUT_PATCH :: UserType pattern $mUSER_TYPE_OUTPUT_PATCH :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_OUTPUT_PATCH :: UserType USER_TYPE_OUTPUT_PATCH = UserType 9 pattern USER_TYPE_RASTERIZER_ORDERED_BUFFER :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_BUFFER :: UserType USER_TYPE_RASTERIZER_ORDERED_BUFFER = UserType 10 pattern USER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER :: UserType USER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER = UserType 11 pattern USER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER :: UserType USER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER = UserType 12 pattern USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D :: UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D = UserType 13 pattern USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY :: UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY = UserType 14 pattern USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D :: UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D = UserType 15 pattern USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY :: UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY = UserType 16 pattern USER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D :: UserType pattern $mUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D :: UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D = UserType 17 pattern USER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE :: UserType pattern $mUSER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE :: UserType USER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE = UserType 18 pattern USER_TYPE_RW_BUFFER :: UserType pattern $mUSER_TYPE_RW_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_BUFFER :: UserType USER_TYPE_RW_BUFFER = UserType 19 pattern USER_TYPE_RW_BYTE_ADDRESS_BUFFER :: UserType pattern $mUSER_TYPE_RW_BYTE_ADDRESS_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_BYTE_ADDRESS_BUFFER :: UserType USER_TYPE_RW_BYTE_ADDRESS_BUFFER = UserType 20 pattern USER_TYPE_RW_STRUCTURED_BUFFER :: UserType pattern $mUSER_TYPE_RW_STRUCTURED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_STRUCTURED_BUFFER :: UserType USER_TYPE_RW_STRUCTURED_BUFFER = UserType 21 pattern USER_TYPE_RW_TEXTURE_1D :: UserType pattern $mUSER_TYPE_RW_TEXTURE_1D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_TEXTURE_1D :: UserType USER_TYPE_RW_TEXTURE_1D = UserType 22 pattern USER_TYPE_RW_TEXTURE_1D_ARRAY :: UserType pattern $mUSER_TYPE_RW_TEXTURE_1D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_TEXTURE_1D_ARRAY :: UserType USER_TYPE_RW_TEXTURE_1D_ARRAY = UserType 23 pattern USER_TYPE_RW_TEXTURE_2D :: UserType pattern $mUSER_TYPE_RW_TEXTURE_2D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_TEXTURE_2D :: UserType USER_TYPE_RW_TEXTURE_2D = UserType 24 pattern USER_TYPE_RW_TEXTURE_2D_ARRAY :: UserType pattern $mUSER_TYPE_RW_TEXTURE_2D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_TEXTURE_2D_ARRAY :: UserType USER_TYPE_RW_TEXTURE_2D_ARRAY = UserType 25 pattern USER_TYPE_RW_TEXTURE_3D :: UserType pattern $mUSER_TYPE_RW_TEXTURE_3D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_RW_TEXTURE_3D :: UserType USER_TYPE_RW_TEXTURE_3D = UserType 26 pattern USER_TYPE_STRUCTURED_BUFFER :: UserType pattern $mUSER_TYPE_STRUCTURED_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_STRUCTURED_BUFFER :: UserType USER_TYPE_STRUCTURED_BUFFER = UserType 27 pattern USER_TYPE_SUBPASS_INPUT :: UserType pattern $mUSER_TYPE_SUBPASS_INPUT :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_SUBPASS_INPUT :: UserType USER_TYPE_SUBPASS_INPUT = UserType 28 pattern USER_TYPE_SUBPASS_INPUT_MS :: UserType pattern $mUSER_TYPE_SUBPASS_INPUT_MS :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_SUBPASS_INPUT_MS :: UserType USER_TYPE_SUBPASS_INPUT_MS = UserType 29 pattern USER_TYPE_TEXTURE_1D :: UserType pattern $mUSER_TYPE_TEXTURE_1D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_1D :: UserType USER_TYPE_TEXTURE_1D = UserType 30 pattern USER_TYPE_TEXTURE_1D_ARRAY :: UserType pattern $mUSER_TYPE_TEXTURE_1D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_1D_ARRAY :: UserType USER_TYPE_TEXTURE_1D_ARRAY = UserType 31 pattern USER_TYPE_TEXTURE_2D :: UserType pattern $mUSER_TYPE_TEXTURE_2D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_2D :: UserType USER_TYPE_TEXTURE_2D = UserType 32 pattern USER_TYPE_TEXTURE_2D_ARRAY :: UserType pattern $mUSER_TYPE_TEXTURE_2D_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_2D_ARRAY :: UserType USER_TYPE_TEXTURE_2D_ARRAY = UserType 33 pattern USER_TYPE_TEXTURE_2DMS :: UserType pattern $mUSER_TYPE_TEXTURE_2DMS :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_2DMS :: UserType USER_TYPE_TEXTURE_2DMS = UserType 34 pattern USER_TYPE_TEXTURE_2DMS_ARRAY :: UserType pattern $mUSER_TYPE_TEXTURE_2DMS_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_2DMS_ARRAY :: UserType USER_TYPE_TEXTURE_2DMS_ARRAY = UserType 35 pattern USER_TYPE_TEXTURE_3D :: UserType pattern $mUSER_TYPE_TEXTURE_3D :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_3D :: UserType USER_TYPE_TEXTURE_3D = UserType 36 pattern USER_TYPE_TEXTURE_BUFFER :: UserType pattern $mUSER_TYPE_TEXTURE_BUFFER :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_BUFFER :: UserType USER_TYPE_TEXTURE_BUFFER = UserType 37 pattern USER_TYPE_TEXTURE_CUBE :: UserType pattern $mUSER_TYPE_TEXTURE_CUBE :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_CUBE :: UserType USER_TYPE_TEXTURE_CUBE = UserType 38 pattern USER_TYPE_TEXTURE_CUBE_ARRAY :: UserType pattern $mUSER_TYPE_TEXTURE_CUBE_ARRAY :: forall {r}. UserType -> ((# #) -> r) -> ((# #) -> r) -> r $bUSER_TYPE_TEXTURE_CUBE_ARRAY :: UserType USER_TYPE_TEXTURE_CUBE_ARRAY = UserType 39 userTypeName :: IsString label => UserType -> Maybe label userTypeName :: forall label. IsString label => UserType -> Maybe label userTypeName = [(UserType, label)] -> UserType -> Maybe label forall i label. Enum i => [(i, label)] -> i -> Maybe label toLabel [(UserType, label)] forall label. IsString label => [(UserType, label)] userTypeNames userTypeNames :: IsString label => [(UserType, label)] userTypeNames :: forall label. IsString label => [(UserType, label)] userTypeNames = [ (UserType USER_TYPE_INVALID, label "Invalid") , (UserType USER_TYPE_CBUFFER, label "cbuffer") , (UserType USER_TYPE_TBUFFER, label "tbuffer") , (UserType USER_TYPE_APPEND_STRUCTURED_BUFFER, label "AppendStructuredBuffer") , (UserType USER_TYPE_BUFFER, label "Buffer") , (UserType USER_TYPE_BYTE_ADDRESS_BUFFER, label "ByteAddressBuffer") , (UserType USER_TYPE_CONSTANT_BUFFER, label "ConstantBuffer") , (UserType USER_TYPE_CONSUME_STRUCTURED_BUFFER, label "ConsumeStructuredBuffer") , (UserType USER_TYPE_INPUT_PATCH, label "InputPatch") , (UserType USER_TYPE_OUTPUT_PATCH, label "OutputPatch") , (UserType USER_TYPE_RASTERIZER_ORDERED_BUFFER, label "RasterizerOrderedBuffer") , (UserType USER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER, label "RasterizerOrderedByteAddressBuffer") , (UserType USER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER, label "RasterizerOrderedStructuredBuffer") , (UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D, label "RasterizerOrderedTexture1D") , (UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY, label "RasterizerOrderedTexture1DArray") , (UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D, label "RasterizerOrderedTexture2D") , (UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY, label "RasterizerOrdered_Texture2DArray") , (UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D, label "RasterizerOrderedTexture3D") , (UserType USER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE, label "RaytracingAccelerationStructure") , (UserType USER_TYPE_RW_BUFFER, label "RWBuffer") , (UserType USER_TYPE_RW_BYTE_ADDRESS_BUFFER, label "RWByteAddressBuffer") , (UserType USER_TYPE_RW_STRUCTURED_BUFFER, label "RWStructuredBuffer") , (UserType USER_TYPE_RW_TEXTURE_1D, label "RWTexture1D") , (UserType USER_TYPE_RW_TEXTURE_1D_ARRAY, label "RWTexture1DArray") , (UserType USER_TYPE_RW_TEXTURE_2D, label "RWTexture2D") , (UserType USER_TYPE_RW_TEXTURE_2D_ARRAY, label "RWTexture2DArray") , (UserType USER_TYPE_RW_TEXTURE_3D, label "RWTexture3D") , (UserType USER_TYPE_STRUCTURED_BUFFER, label "StructuredBuffer") , (UserType USER_TYPE_SUBPASS_INPUT, label "SubpassInput") , (UserType USER_TYPE_SUBPASS_INPUT_MS, label "SubpassInputMS") , (UserType USER_TYPE_TEXTURE_1D, label "Texture1D") , (UserType USER_TYPE_TEXTURE_1D_ARRAY, label "Texture1DArray") , (UserType USER_TYPE_TEXTURE_2D, label "Texture2D") , (UserType USER_TYPE_TEXTURE_2D_ARRAY, label "Texture2DArray") , (UserType USER_TYPE_TEXTURE_2DMS, label "Texture2DMS") , (UserType USER_TYPE_TEXTURE_2DMS_ARRAY, label "Texture2DMSArray") , (UserType USER_TYPE_TEXTURE_3D, label "Texture3D") , (UserType USER_TYPE_TEXTURE_BUFFER, label "TextureBuffer") , (UserType USER_TYPE_TEXTURE_CUBE, label "TextureCube") , (UserType USER_TYPE_TEXTURE_CUBE_ARRAY, label "TextureCubeArray") ] userTypeId :: (Eq label, IsString label) => label -> Maybe UserType userTypeId :: forall label. (Eq label, IsString label) => label -> Maybe UserType userTypeId = \case label "Invalid" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_INVALID label "cbuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_CBUFFER label "tbuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TBUFFER label "AppendStructuredBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_APPEND_STRUCTURED_BUFFER label "Buffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_BUFFER label "ByteAddressBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_BYTE_ADDRESS_BUFFER label "ConstantBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_CONSTANT_BUFFER label "ConsumeStructuredBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_CONSUME_STRUCTURED_BUFFER label "InputPatch" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_INPUT_PATCH label "OutputPatch" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_OUTPUT_PATCH label "RasterizerOrderedBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_BUFFER label "RasterizerOrderedByteAddressBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_BYTE_ADDRESS_BUFFER label "RasterizerOrderedStructuredBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_STRUCTURED_BUFFER label "RasterizerOrderedTexture1D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D label "RasterizerOrderedTexture1DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_1D_ARRAY label "RasterizerOrderedTexture2D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D label "RasterizerOrderedTexture2DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_2D_ARRAY label "RasterizerOrderedTexture3D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RASTERIZER_ORDERED_TEXTURE_3D label "RaytracingAccelerationStructure" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RAYTRACING_ACCELERATION_STRUCTURE label "RWBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_BUFFER label "RWByteAddressBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_BYTE_ADDRESS_BUFFER label "RWStructuredBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_STRUCTURED_BUFFER label "RWTexture1D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_TEXTURE_1D label "RWTexture1DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_TEXTURE_1D_ARRAY label "RWTexture2D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_TEXTURE_2D label "RWTexture2DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_TEXTURE_2D_ARRAY label "RWTexture3D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_RW_TEXTURE_3D label "StructuredBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_STRUCTURED_BUFFER label "SubpassInput" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_SUBPASS_INPUT label "SubpassInputMs" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_SUBPASS_INPUT_MS label "Texture1D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_1D label "Texture1DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_1D_ARRAY label "Texture2D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_2D label "Texture2DArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_2D_ARRAY label "Texture2DMS" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_2DMS label "Texture2DMSArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_2DMS_ARRAY label "Texture3D" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_3D label "TextureBuffer" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_BUFFER label "TextureCube" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_CUBE label "TextureCubeArray" -> UserType -> Maybe UserType forall a. a -> Maybe a Just UserType USER_TYPE_TEXTURE_CUBE_ARRAY label _ -> Maybe UserType forall a. Maybe a Nothing