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