module Data.SpirV.Enum.RayQueryIntersection 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 RayQueryIntersection = RayQueryIntersection Word32 deriving (Eq, Ord, Storable) pattern RayQueryCandidateIntersectionKHR :: RayQueryIntersection pattern RayQueryCandidateIntersectionKHR = RayQueryIntersection 0 pattern RayQueryCommittedIntersectionKHR :: RayQueryIntersection pattern RayQueryCommittedIntersectionKHR = RayQueryIntersection 1 toName :: IsString a => RayQueryIntersection -> a toName x = case x of RayQueryCandidateIntersectionKHR -> "RayQueryCandidateIntersectionKHR" RayQueryCommittedIntersectionKHR -> "RayQueryCommittedIntersectionKHR" unknown -> fromString $ "RayQueryIntersection " ++ show unknown instance Show RayQueryIntersection where show = toName fromName :: (IsString a, Eq a) => a -> Maybe RayQueryIntersection fromName x = case x of "RayQueryCandidateIntersectionKHR" -> Just RayQueryCandidateIntersectionKHR "RayQueryCommittedIntersectionKHR" -> Just RayQueryCommittedIntersectionKHR _unknown -> Nothing instance Read RayQueryIntersection where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s