{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TypeSynonymInstances #-} module Data.SpirV.Enum.CooperativeMatrixOperands where import Data.Bits (Bits, FiniteBits, (.|.)) import Data.Word (Word32) import Foreign.Storable (Storable) type CooperativeMatrixOperands = CooperativeMatrixOperandsBits newtype CooperativeMatrixOperandsBits = CooperativeMatrixOperandsBits Word32 deriving newtype (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> Eq CooperativeMatrixOperandsBits forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool == :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool $c/= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool /= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool Eq, Eq CooperativeMatrixOperandsBits Eq CooperativeMatrixOperandsBits => (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Ordering) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> Ord CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Ordering CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits 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 :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Ordering compare :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Ordering $c< :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool < :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool $c<= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool <= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool $c> :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool > :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool $c>= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool >= :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> Bool $cmax :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits max :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits $cmin :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits min :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits Ord, Ptr CooperativeMatrixOperandsBits -> IO CooperativeMatrixOperandsBits Ptr CooperativeMatrixOperandsBits -> Int -> IO CooperativeMatrixOperandsBits Ptr CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits -> IO () Ptr CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> IO () CooperativeMatrixOperandsBits -> Int (CooperativeMatrixOperandsBits -> Int) -> (CooperativeMatrixOperandsBits -> Int) -> (Ptr CooperativeMatrixOperandsBits -> Int -> IO CooperativeMatrixOperandsBits) -> (Ptr CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits -> IO ()) -> (forall b. Ptr b -> Int -> IO CooperativeMatrixOperandsBits) -> (forall b. Ptr b -> Int -> CooperativeMatrixOperandsBits -> IO ()) -> (Ptr CooperativeMatrixOperandsBits -> IO CooperativeMatrixOperandsBits) -> (Ptr CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> IO ()) -> Storable CooperativeMatrixOperandsBits forall b. Ptr b -> Int -> IO CooperativeMatrixOperandsBits forall b. Ptr b -> Int -> CooperativeMatrixOperandsBits -> 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 :: CooperativeMatrixOperandsBits -> Int sizeOf :: CooperativeMatrixOperandsBits -> Int $calignment :: CooperativeMatrixOperandsBits -> Int alignment :: CooperativeMatrixOperandsBits -> Int $cpeekElemOff :: Ptr CooperativeMatrixOperandsBits -> Int -> IO CooperativeMatrixOperandsBits peekElemOff :: Ptr CooperativeMatrixOperandsBits -> Int -> IO CooperativeMatrixOperandsBits $cpokeElemOff :: Ptr CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits -> IO () pokeElemOff :: Ptr CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits -> IO () $cpeekByteOff :: forall b. Ptr b -> Int -> IO CooperativeMatrixOperandsBits peekByteOff :: forall b. Ptr b -> Int -> IO CooperativeMatrixOperandsBits $cpokeByteOff :: forall b. Ptr b -> Int -> CooperativeMatrixOperandsBits -> IO () pokeByteOff :: forall b. Ptr b -> Int -> CooperativeMatrixOperandsBits -> IO () $cpeek :: Ptr CooperativeMatrixOperandsBits -> IO CooperativeMatrixOperandsBits peek :: Ptr CooperativeMatrixOperandsBits -> IO CooperativeMatrixOperandsBits $cpoke :: Ptr CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> IO () poke :: Ptr CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> IO () Storable, Eq CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits Eq CooperativeMatrixOperandsBits => (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> CooperativeMatrixOperandsBits -> (Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> Bool) -> (CooperativeMatrixOperandsBits -> Maybe Int) -> (CooperativeMatrixOperandsBits -> Int) -> (CooperativeMatrixOperandsBits -> Bool) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits) -> (CooperativeMatrixOperandsBits -> Int) -> Bits CooperativeMatrixOperandsBits Int -> CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits -> Bool CooperativeMatrixOperandsBits -> Int CooperativeMatrixOperandsBits -> Maybe Int CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits -> Int -> Bool CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits forall a. Eq a => (a -> a -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> a -> (Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> Bool) -> (a -> Maybe Int) -> (a -> Int) -> (a -> Bool) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int -> a) -> (a -> Int) -> Bits a $c.&. :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits .&. :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits $c.|. :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits .|. :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits $cxor :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits xor :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits $ccomplement :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits complement :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits $cshift :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits shift :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $crotate :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits rotate :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $czeroBits :: CooperativeMatrixOperandsBits zeroBits :: CooperativeMatrixOperandsBits $cbit :: Int -> CooperativeMatrixOperandsBits bit :: Int -> CooperativeMatrixOperandsBits $csetBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits setBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $cclearBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits clearBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $ccomplementBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits complementBit :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $ctestBit :: CooperativeMatrixOperandsBits -> Int -> Bool testBit :: CooperativeMatrixOperandsBits -> Int -> Bool $cbitSizeMaybe :: CooperativeMatrixOperandsBits -> Maybe Int bitSizeMaybe :: CooperativeMatrixOperandsBits -> Maybe Int $cbitSize :: CooperativeMatrixOperandsBits -> Int bitSize :: CooperativeMatrixOperandsBits -> Int $cisSigned :: CooperativeMatrixOperandsBits -> Bool isSigned :: CooperativeMatrixOperandsBits -> Bool $cshiftL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits shiftL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $cunsafeShiftL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits unsafeShiftL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $cshiftR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits shiftR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $cunsafeShiftR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits unsafeShiftR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $crotateL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits rotateL :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $crotateR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits rotateR :: CooperativeMatrixOperandsBits -> Int -> CooperativeMatrixOperandsBits $cpopCount :: CooperativeMatrixOperandsBits -> Int popCount :: CooperativeMatrixOperandsBits -> Int Bits, Bits CooperativeMatrixOperandsBits Bits CooperativeMatrixOperandsBits => (CooperativeMatrixOperandsBits -> Int) -> (CooperativeMatrixOperandsBits -> Int) -> (CooperativeMatrixOperandsBits -> Int) -> FiniteBits CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits -> Int forall b. Bits b => (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b $cfiniteBitSize :: CooperativeMatrixOperandsBits -> Int finiteBitSize :: CooperativeMatrixOperandsBits -> Int $ccountLeadingZeros :: CooperativeMatrixOperandsBits -> Int countLeadingZeros :: CooperativeMatrixOperandsBits -> Int $ccountTrailingZeros :: CooperativeMatrixOperandsBits -> Int countTrailingZeros :: CooperativeMatrixOperandsBits -> Int FiniteBits) instance Semigroup CooperativeMatrixOperands where (CooperativeMatrixOperandsBits Word32 a) <> :: CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits -> CooperativeMatrixOperandsBits <> (CooperativeMatrixOperandsBits Word32 b) = Word32 -> CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits (Word32 a Word32 -> Word32 -> Word32 forall a. Bits a => a -> a -> a .|. Word32 b) instance Monoid CooperativeMatrixOperands where mempty :: CooperativeMatrixOperandsBits mempty = Word32 -> CooperativeMatrixOperandsBits CooperativeMatrixOperandsBits Word32 0 pattern MatrixASignedComponentsKHR :: CooperativeMatrixOperandsBits pattern $mMatrixASignedComponentsKHR :: forall {r}. CooperativeMatrixOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r $bMatrixASignedComponentsKHR :: CooperativeMatrixOperandsBits MatrixASignedComponentsKHR = CooperativeMatrixOperandsBits 0x00000001 pattern MatrixBSignedComponentsKHR :: CooperativeMatrixOperandsBits pattern $mMatrixBSignedComponentsKHR :: forall {r}. CooperativeMatrixOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r $bMatrixBSignedComponentsKHR :: CooperativeMatrixOperandsBits MatrixBSignedComponentsKHR = CooperativeMatrixOperandsBits 0x00000002 pattern MatrixCSignedComponentsKHR :: CooperativeMatrixOperandsBits pattern $mMatrixCSignedComponentsKHR :: forall {r}. CooperativeMatrixOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r $bMatrixCSignedComponentsKHR :: CooperativeMatrixOperandsBits MatrixCSignedComponentsKHR = CooperativeMatrixOperandsBits 0x00000004 pattern MatrixResultSignedComponentsKHR :: CooperativeMatrixOperandsBits pattern $mMatrixResultSignedComponentsKHR :: forall {r}. CooperativeMatrixOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r $bMatrixResultSignedComponentsKHR :: CooperativeMatrixOperandsBits MatrixResultSignedComponentsKHR = CooperativeMatrixOperandsBits 0x00000008 pattern SaturatingAccumulationKHR :: CooperativeMatrixOperandsBits pattern $mSaturatingAccumulationKHR :: forall {r}. CooperativeMatrixOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r $bSaturatingAccumulationKHR :: CooperativeMatrixOperandsBits SaturatingAccumulationKHR = CooperativeMatrixOperandsBits 0x00000010