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