module Data.SpirV.Enum.RayQueryCommittedIntersectionType where import Data.String (IsString(..)) import Data.Word (Word32) import Foreign (Storable(..)) import GHC.Read (Read(..)) import Text.ParserCombinators.ReadPrec (pfail) import qualified GHC.Read as Read import qualified Text.Read.Lex as Lex newtype RayQueryCommittedIntersectionType = RayQueryCommittedIntersectionType Word32 deriving (Eq, Ord, Storable) pattern RayQueryCommittedIntersectionNoneKHR :: RayQueryCommittedIntersectionType pattern RayQueryCommittedIntersectionNoneKHR = RayQueryCommittedIntersectionType 0 pattern RayQueryCommittedIntersectionTriangleKHR :: RayQueryCommittedIntersectionType pattern RayQueryCommittedIntersectionTriangleKHR = RayQueryCommittedIntersectionType 1 pattern RayQueryCommittedIntersectionGeneratedKHR :: RayQueryCommittedIntersectionType pattern RayQueryCommittedIntersectionGeneratedKHR = RayQueryCommittedIntersectionType 2 toName :: IsString a => RayQueryCommittedIntersectionType -> a toName x = case x of RayQueryCommittedIntersectionNoneKHR -> "RayQueryCommittedIntersectionNoneKHR" RayQueryCommittedIntersectionTriangleKHR -> "RayQueryCommittedIntersectionTriangleKHR" RayQueryCommittedIntersectionGeneratedKHR -> "RayQueryCommittedIntersectionGeneratedKHR" unknown -> fromString $ "RayQueryCommittedIntersectionType " ++ show unknown instance Show RayQueryCommittedIntersectionType where show = toName fromName :: (IsString a, Eq a) => a -> Maybe RayQueryCommittedIntersectionType fromName x = case x of "RayQueryCommittedIntersectionNoneKHR" -> Just RayQueryCommittedIntersectionNoneKHR "RayQueryCommittedIntersectionTriangleKHR" -> Just RayQueryCommittedIntersectionTriangleKHR "RayQueryCommittedIntersectionGeneratedKHR" -> Just RayQueryCommittedIntersectionGeneratedKHR _unknown -> Nothing instance Read RayQueryCommittedIntersectionType where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s