module Data.SpirV.Reflect.Enums.DescriptorType where import Data.SpirV.Reflect.Enums.Common newtype DescriptorType = DescriptorType Int deriving newtype (DescriptorType -> DescriptorType -> Bool (DescriptorType -> DescriptorType -> Bool) -> (DescriptorType -> DescriptorType -> Bool) -> Eq DescriptorType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DescriptorType -> DescriptorType -> Bool $c/= :: DescriptorType -> DescriptorType -> Bool == :: DescriptorType -> DescriptorType -> Bool $c== :: DescriptorType -> DescriptorType -> Bool Eq, Eq DescriptorType Eq DescriptorType -> (DescriptorType -> DescriptorType -> Ordering) -> (DescriptorType -> DescriptorType -> Bool) -> (DescriptorType -> DescriptorType -> Bool) -> (DescriptorType -> DescriptorType -> Bool) -> (DescriptorType -> DescriptorType -> Bool) -> (DescriptorType -> DescriptorType -> DescriptorType) -> (DescriptorType -> DescriptorType -> DescriptorType) -> Ord DescriptorType DescriptorType -> DescriptorType -> Bool DescriptorType -> DescriptorType -> Ordering DescriptorType -> DescriptorType -> DescriptorType 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 :: DescriptorType -> DescriptorType -> DescriptorType $cmin :: DescriptorType -> DescriptorType -> DescriptorType max :: DescriptorType -> DescriptorType -> DescriptorType $cmax :: DescriptorType -> DescriptorType -> DescriptorType >= :: DescriptorType -> DescriptorType -> Bool $c>= :: DescriptorType -> DescriptorType -> Bool > :: DescriptorType -> DescriptorType -> Bool $c> :: DescriptorType -> DescriptorType -> Bool <= :: DescriptorType -> DescriptorType -> Bool $c<= :: DescriptorType -> DescriptorType -> Bool < :: DescriptorType -> DescriptorType -> Bool $c< :: DescriptorType -> DescriptorType -> Bool compare :: DescriptorType -> DescriptorType -> Ordering $ccompare :: DescriptorType -> DescriptorType -> Ordering $cp1Ord :: Eq DescriptorType Ord, Int -> DescriptorType -> ShowS [DescriptorType] -> ShowS DescriptorType -> String (Int -> DescriptorType -> ShowS) -> (DescriptorType -> String) -> ([DescriptorType] -> ShowS) -> Show DescriptorType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DescriptorType] -> ShowS $cshowList :: [DescriptorType] -> ShowS show :: DescriptorType -> String $cshow :: DescriptorType -> String showsPrec :: Int -> DescriptorType -> ShowS $cshowsPrec :: Int -> DescriptorType -> ShowS Show, Int -> DescriptorType DescriptorType -> Int DescriptorType -> [DescriptorType] DescriptorType -> DescriptorType DescriptorType -> DescriptorType -> [DescriptorType] DescriptorType -> DescriptorType -> DescriptorType -> [DescriptorType] (DescriptorType -> DescriptorType) -> (DescriptorType -> DescriptorType) -> (Int -> DescriptorType) -> (DescriptorType -> Int) -> (DescriptorType -> [DescriptorType]) -> (DescriptorType -> DescriptorType -> [DescriptorType]) -> (DescriptorType -> DescriptorType -> [DescriptorType]) -> (DescriptorType -> DescriptorType -> DescriptorType -> [DescriptorType]) -> Enum DescriptorType forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a enumFromThenTo :: DescriptorType -> DescriptorType -> DescriptorType -> [DescriptorType] $cenumFromThenTo :: DescriptorType -> DescriptorType -> DescriptorType -> [DescriptorType] enumFromTo :: DescriptorType -> DescriptorType -> [DescriptorType] $cenumFromTo :: DescriptorType -> DescriptorType -> [DescriptorType] enumFromThen :: DescriptorType -> DescriptorType -> [DescriptorType] $cenumFromThen :: DescriptorType -> DescriptorType -> [DescriptorType] enumFrom :: DescriptorType -> [DescriptorType] $cenumFrom :: DescriptorType -> [DescriptorType] fromEnum :: DescriptorType -> Int $cfromEnum :: DescriptorType -> Int toEnum :: Int -> DescriptorType $ctoEnum :: Int -> DescriptorType pred :: DescriptorType -> DescriptorType $cpred :: DescriptorType -> DescriptorType succ :: DescriptorType -> DescriptorType $csucc :: DescriptorType -> DescriptorType Enum) pattern DESCRIPTOR_TYPE_SAMPLER :: DescriptorType pattern $bDESCRIPTOR_TYPE_SAMPLER :: DescriptorType $mDESCRIPTOR_TYPE_SAMPLER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_SAMPLER = DescriptorType 0 pattern DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER :: DescriptorType pattern $bDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER :: DescriptorType $mDESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER = DescriptorType 1 pattern DESCRIPTOR_TYPE_SAMPLED_IMAGE :: DescriptorType pattern $bDESCRIPTOR_TYPE_SAMPLED_IMAGE :: DescriptorType $mDESCRIPTOR_TYPE_SAMPLED_IMAGE :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_SAMPLED_IMAGE = DescriptorType 2 pattern DESCRIPTOR_TYPE_STORAGE_IMAGE :: DescriptorType pattern $bDESCRIPTOR_TYPE_STORAGE_IMAGE :: DescriptorType $mDESCRIPTOR_TYPE_STORAGE_IMAGE :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_STORAGE_IMAGE = DescriptorType 3 pattern DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER :: DescriptorType pattern $bDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER :: DescriptorType $mDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER = DescriptorType 4 pattern DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER :: DescriptorType pattern $bDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER :: DescriptorType $mDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER = DescriptorType 5 pattern DESCRIPTOR_TYPE_UNIFORM_BUFFER :: DescriptorType pattern $bDESCRIPTOR_TYPE_UNIFORM_BUFFER :: DescriptorType $mDESCRIPTOR_TYPE_UNIFORM_BUFFER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_UNIFORM_BUFFER = DescriptorType 6 pattern DESCRIPTOR_TYPE_STORAGE_BUFFER :: DescriptorType pattern $bDESCRIPTOR_TYPE_STORAGE_BUFFER :: DescriptorType $mDESCRIPTOR_TYPE_STORAGE_BUFFER :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_STORAGE_BUFFER = DescriptorType 7 pattern DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC :: DescriptorType pattern $bDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC :: DescriptorType $mDESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC = DescriptorType 8 pattern DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC :: DescriptorType pattern $bDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC :: DescriptorType $mDESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC = DescriptorType 9 pattern DESCRIPTOR_TYPE_INPUT_ATTACHMENT :: DescriptorType pattern $bDESCRIPTOR_TYPE_INPUT_ATTACHMENT :: DescriptorType $mDESCRIPTOR_TYPE_INPUT_ATTACHMENT :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_INPUT_ATTACHMENT = DescriptorType 10 pattern DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR :: DescriptorType pattern $bDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR :: DescriptorType $mDESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR :: forall r. DescriptorType -> (Void# -> r) -> (Void# -> r) -> r DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR = DescriptorType 1000150000 descriptorTypeName :: IsString label => DescriptorType -> Maybe label descriptorTypeName :: DescriptorType -> Maybe label descriptorTypeName = [(DescriptorType, label)] -> DescriptorType -> Maybe label forall i label. Enum i => [(i, label)] -> i -> Maybe label toLabel [(DescriptorType, label)] forall label. IsString label => [(DescriptorType, label)] descriptorTypeNames descriptorTypeNames :: IsString label => [(DescriptorType, label)] descriptorTypeNames :: [(DescriptorType, label)] descriptorTypeNames = [ (DescriptorType DESCRIPTOR_TYPE_SAMPLER, label "SAMPLER") , (DescriptorType DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER, label "COMBINED_IMAGE_SAMPLER") , (DescriptorType DESCRIPTOR_TYPE_SAMPLED_IMAGE, label "SAMPLED_IMAGE") , (DescriptorType DESCRIPTOR_TYPE_STORAGE_IMAGE, label "STORAGE_IMAGE") , (DescriptorType DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER, label "UNIFORM_TEXEL_BUFFER") , (DescriptorType DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER, label "STORAGE_TEXEL_BUFFER") , (DescriptorType DESCRIPTOR_TYPE_UNIFORM_BUFFER, label "UNIFORM_BUFFER") , (DescriptorType DESCRIPTOR_TYPE_STORAGE_BUFFER, label "STORAGE_BUFFER") , (DescriptorType DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC, label "UNIFORM_BUFFER_DYNAMIC") , (DescriptorType DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC, label "STORAGE_BUFFER_DYNAMIC") , (DescriptorType DESCRIPTOR_TYPE_INPUT_ATTACHMENT, label "INPUT_ATTACHMENT") , (DescriptorType DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR, label "ACCELERATION_STRUCTURE_KHR") ]