{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TypeSynonymInstances #-} module Data.SpirV.Enum.RayQueryCommittedIntersectionType where import Data.Word (Word32) import Foreign.Storable (Storable) newtype RayQueryCommittedIntersectionType = RayQueryCommittedIntersectionType Word32 deriving newtype (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> Eq RayQueryCommittedIntersectionType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool == :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool $c/= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool /= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool Eq, Eq RayQueryCommittedIntersectionType Eq RayQueryCommittedIntersectionType => (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Ordering) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType) -> (RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType) -> Ord RayQueryCommittedIntersectionType RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Ordering RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType 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 :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Ordering compare :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Ordering $c< :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool < :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool $c<= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool <= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool $c> :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool > :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool $c>= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool >= :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> Bool $cmax :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType max :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType $cmin :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType min :: RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType Ord, Ptr RayQueryCommittedIntersectionType -> IO RayQueryCommittedIntersectionType Ptr RayQueryCommittedIntersectionType -> Int -> IO RayQueryCommittedIntersectionType Ptr RayQueryCommittedIntersectionType -> Int -> RayQueryCommittedIntersectionType -> IO () Ptr RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> IO () RayQueryCommittedIntersectionType -> Int (RayQueryCommittedIntersectionType -> Int) -> (RayQueryCommittedIntersectionType -> Int) -> (Ptr RayQueryCommittedIntersectionType -> Int -> IO RayQueryCommittedIntersectionType) -> (Ptr RayQueryCommittedIntersectionType -> Int -> RayQueryCommittedIntersectionType -> IO ()) -> (forall b. Ptr b -> Int -> IO RayQueryCommittedIntersectionType) -> (forall b. Ptr b -> Int -> RayQueryCommittedIntersectionType -> IO ()) -> (Ptr RayQueryCommittedIntersectionType -> IO RayQueryCommittedIntersectionType) -> (Ptr RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> IO ()) -> Storable RayQueryCommittedIntersectionType forall b. Ptr b -> Int -> IO RayQueryCommittedIntersectionType forall b. Ptr b -> Int -> RayQueryCommittedIntersectionType -> 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 :: RayQueryCommittedIntersectionType -> Int sizeOf :: RayQueryCommittedIntersectionType -> Int $calignment :: RayQueryCommittedIntersectionType -> Int alignment :: RayQueryCommittedIntersectionType -> Int $cpeekElemOff :: Ptr RayQueryCommittedIntersectionType -> Int -> IO RayQueryCommittedIntersectionType peekElemOff :: Ptr RayQueryCommittedIntersectionType -> Int -> IO RayQueryCommittedIntersectionType $cpokeElemOff :: Ptr RayQueryCommittedIntersectionType -> Int -> RayQueryCommittedIntersectionType -> IO () pokeElemOff :: Ptr RayQueryCommittedIntersectionType -> Int -> RayQueryCommittedIntersectionType -> IO () $cpeekByteOff :: forall b. Ptr b -> Int -> IO RayQueryCommittedIntersectionType peekByteOff :: forall b. Ptr b -> Int -> IO RayQueryCommittedIntersectionType $cpokeByteOff :: forall b. Ptr b -> Int -> RayQueryCommittedIntersectionType -> IO () pokeByteOff :: forall b. Ptr b -> Int -> RayQueryCommittedIntersectionType -> IO () $cpeek :: Ptr RayQueryCommittedIntersectionType -> IO RayQueryCommittedIntersectionType peek :: Ptr RayQueryCommittedIntersectionType -> IO RayQueryCommittedIntersectionType $cpoke :: Ptr RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> IO () poke :: Ptr RayQueryCommittedIntersectionType -> RayQueryCommittedIntersectionType -> IO () Storable) instance Show RayQueryCommittedIntersectionType where showsPrec :: Int -> RayQueryCommittedIntersectionType -> ShowS showsPrec Int p (RayQueryCommittedIntersectionType Word32 v) = case Word32 v of Word32 0 -> String -> ShowS showString String "RayQueryCommittedIntersectionNoneKHR" Word32 1 -> String -> ShowS showString String "RayQueryCommittedIntersectionTriangleKHR" Word32 2 -> String -> ShowS showString String "RayQueryCommittedIntersectionGeneratedKHR" 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 "RayQueryCommittedIntersectionType " 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 RayQueryCommittedIntersectionNoneKHR :: RayQueryCommittedIntersectionType pattern $mRayQueryCommittedIntersectionNoneKHR :: forall {r}. RayQueryCommittedIntersectionType -> ((# #) -> r) -> ((# #) -> r) -> r $bRayQueryCommittedIntersectionNoneKHR :: RayQueryCommittedIntersectionType RayQueryCommittedIntersectionNoneKHR = RayQueryCommittedIntersectionType 0 pattern RayQueryCommittedIntersectionTriangleKHR :: RayQueryCommittedIntersectionType pattern $mRayQueryCommittedIntersectionTriangleKHR :: forall {r}. RayQueryCommittedIntersectionType -> ((# #) -> r) -> ((# #) -> r) -> r $bRayQueryCommittedIntersectionTriangleKHR :: RayQueryCommittedIntersectionType RayQueryCommittedIntersectionTriangleKHR = RayQueryCommittedIntersectionType 1 pattern RayQueryCommittedIntersectionGeneratedKHR :: RayQueryCommittedIntersectionType pattern $mRayQueryCommittedIntersectionGeneratedKHR :: forall {r}. RayQueryCommittedIntersectionType -> ((# #) -> r) -> ((# #) -> r) -> r $bRayQueryCommittedIntersectionGeneratedKHR :: RayQueryCommittedIntersectionType RayQueryCommittedIntersectionGeneratedKHR = RayQueryCommittedIntersectionType 2