{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TypeSynonymInstances #-} module Data.SpirV.Enum.RayQueryCandidateIntersectionType where import Data.Word (Word32) import Foreign.Storable (Storable) newtype RayQueryCandidateIntersectionType = RayQueryCandidateIntersectionType Word32 deriving newtype (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> Eq RayQueryCandidateIntersectionType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool == :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool $c/= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool /= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool Eq, Eq RayQueryCandidateIntersectionType Eq RayQueryCandidateIntersectionType => (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Ordering) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType) -> (RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType) -> Ord RayQueryCandidateIntersectionType RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Ordering RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType 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 :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Ordering compare :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Ordering $c< :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool < :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool $c<= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool <= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool $c> :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool > :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool $c>= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool >= :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> Bool $cmax :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType max :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType $cmin :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType min :: RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType Ord, Ptr RayQueryCandidateIntersectionType -> IO RayQueryCandidateIntersectionType Ptr RayQueryCandidateIntersectionType -> Int -> IO RayQueryCandidateIntersectionType Ptr RayQueryCandidateIntersectionType -> Int -> RayQueryCandidateIntersectionType -> IO () Ptr RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> IO () RayQueryCandidateIntersectionType -> Int (RayQueryCandidateIntersectionType -> Int) -> (RayQueryCandidateIntersectionType -> Int) -> (Ptr RayQueryCandidateIntersectionType -> Int -> IO RayQueryCandidateIntersectionType) -> (Ptr RayQueryCandidateIntersectionType -> Int -> RayQueryCandidateIntersectionType -> IO ()) -> (forall b. Ptr b -> Int -> IO RayQueryCandidateIntersectionType) -> (forall b. Ptr b -> Int -> RayQueryCandidateIntersectionType -> IO ()) -> (Ptr RayQueryCandidateIntersectionType -> IO RayQueryCandidateIntersectionType) -> (Ptr RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> IO ()) -> Storable RayQueryCandidateIntersectionType forall b. Ptr b -> Int -> IO RayQueryCandidateIntersectionType forall b. Ptr b -> Int -> RayQueryCandidateIntersectionType -> 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 $csizeOf :: RayQueryCandidateIntersectionType -> Int sizeOf :: RayQueryCandidateIntersectionType -> Int $calignment :: RayQueryCandidateIntersectionType -> Int alignment :: RayQueryCandidateIntersectionType -> Int $cpeekElemOff :: Ptr RayQueryCandidateIntersectionType -> Int -> IO RayQueryCandidateIntersectionType peekElemOff :: Ptr RayQueryCandidateIntersectionType -> Int -> IO RayQueryCandidateIntersectionType $cpokeElemOff :: Ptr RayQueryCandidateIntersectionType -> Int -> RayQueryCandidateIntersectionType -> IO () pokeElemOff :: Ptr RayQueryCandidateIntersectionType -> Int -> RayQueryCandidateIntersectionType -> IO () $cpeekByteOff :: forall b. Ptr b -> Int -> IO RayQueryCandidateIntersectionType peekByteOff :: forall b. Ptr b -> Int -> IO RayQueryCandidateIntersectionType $cpokeByteOff :: forall b. Ptr b -> Int -> RayQueryCandidateIntersectionType -> IO () pokeByteOff :: forall b. Ptr b -> Int -> RayQueryCandidateIntersectionType -> IO () $cpeek :: Ptr RayQueryCandidateIntersectionType -> IO RayQueryCandidateIntersectionType peek :: Ptr RayQueryCandidateIntersectionType -> IO RayQueryCandidateIntersectionType $cpoke :: Ptr RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> IO () poke :: Ptr RayQueryCandidateIntersectionType -> RayQueryCandidateIntersectionType -> IO () Storable) instance Show RayQueryCandidateIntersectionType where showsPrec :: Int -> RayQueryCandidateIntersectionType -> ShowS showsPrec Int p (RayQueryCandidateIntersectionType Word32 v) = case Word32 v of Word32 0 -> String -> ShowS showString String "RayQueryCandidateIntersectionTriangleKHR" Word32 1 -> String -> ShowS showString String "RayQueryCandidateIntersectionAABBKHR" Word32 x -> Bool -> ShowS -> ShowS showParen (Int p Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "RayQueryCandidateIntersectionType " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Word32 -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec (Int p Int -> Int -> Int forall a. Num a => a -> a -> a + Int 1) Word32 x pattern RayQueryCandidateIntersectionTriangleKHR :: RayQueryCandidateIntersectionType pattern $mRayQueryCandidateIntersectionTriangleKHR :: forall {r}. RayQueryCandidateIntersectionType -> ((# #) -> r) -> ((# #) -> r) -> r $bRayQueryCandidateIntersectionTriangleKHR :: RayQueryCandidateIntersectionType RayQueryCandidateIntersectionTriangleKHR = RayQueryCandidateIntersectionType 0 pattern RayQueryCandidateIntersectionAABBKHR :: RayQueryCandidateIntersectionType pattern $mRayQueryCandidateIntersectionAABBKHR :: forall {r}. RayQueryCandidateIntersectionType -> ((# #) -> r) -> ((# #) -> r) -> r $bRayQueryCandidateIntersectionAABBKHR :: RayQueryCandidateIntersectionType RayQueryCandidateIntersectionAABBKHR = RayQueryCandidateIntersectionType 1