module Data.SpirV.Reflect.Enums.TypeFlags where import Control.Monad (guard) import Data.SpirV.Reflect.Enums.Common type TypeFlags = TypeFlagBits newtype TypeFlagBits = TypeFlagBits Flags deriving newtype (TypeFlagBits -> TypeFlagBits -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TypeFlagBits -> TypeFlagBits -> Bool $c/= :: TypeFlagBits -> TypeFlagBits -> Bool == :: TypeFlagBits -> TypeFlagBits -> Bool $c== :: TypeFlagBits -> TypeFlagBits -> Bool Eq, Eq TypeFlagBits TypeFlagBits -> TypeFlagBits -> Bool TypeFlagBits -> TypeFlagBits -> Ordering TypeFlagBits -> TypeFlagBits -> TypeFlagBits 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 min :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits $cmin :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits max :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits $cmax :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits >= :: TypeFlagBits -> TypeFlagBits -> Bool $c>= :: TypeFlagBits -> TypeFlagBits -> Bool > :: TypeFlagBits -> TypeFlagBits -> Bool $c> :: TypeFlagBits -> TypeFlagBits -> Bool <= :: TypeFlagBits -> TypeFlagBits -> Bool $c<= :: TypeFlagBits -> TypeFlagBits -> Bool < :: TypeFlagBits -> TypeFlagBits -> Bool $c< :: TypeFlagBits -> TypeFlagBits -> Bool compare :: TypeFlagBits -> TypeFlagBits -> Ordering $ccompare :: TypeFlagBits -> TypeFlagBits -> Ordering Ord, Int -> TypeFlagBits -> ShowS [TypeFlagBits] -> ShowS TypeFlagBits -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TypeFlagBits] -> ShowS $cshowList :: [TypeFlagBits] -> ShowS show :: TypeFlagBits -> String $cshow :: TypeFlagBits -> String showsPrec :: Int -> TypeFlagBits -> ShowS $cshowsPrec :: Int -> TypeFlagBits -> ShowS Show, Eq TypeFlagBits TypeFlagBits Int -> TypeFlagBits TypeFlagBits -> Bool TypeFlagBits -> Int TypeFlagBits -> Maybe Int TypeFlagBits -> TypeFlagBits TypeFlagBits -> Int -> Bool TypeFlagBits -> Int -> TypeFlagBits TypeFlagBits -> TypeFlagBits -> TypeFlagBits 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 popCount :: TypeFlagBits -> Int $cpopCount :: TypeFlagBits -> Int rotateR :: TypeFlagBits -> Int -> TypeFlagBits $crotateR :: TypeFlagBits -> Int -> TypeFlagBits rotateL :: TypeFlagBits -> Int -> TypeFlagBits $crotateL :: TypeFlagBits -> Int -> TypeFlagBits unsafeShiftR :: TypeFlagBits -> Int -> TypeFlagBits $cunsafeShiftR :: TypeFlagBits -> Int -> TypeFlagBits shiftR :: TypeFlagBits -> Int -> TypeFlagBits $cshiftR :: TypeFlagBits -> Int -> TypeFlagBits unsafeShiftL :: TypeFlagBits -> Int -> TypeFlagBits $cunsafeShiftL :: TypeFlagBits -> Int -> TypeFlagBits shiftL :: TypeFlagBits -> Int -> TypeFlagBits $cshiftL :: TypeFlagBits -> Int -> TypeFlagBits isSigned :: TypeFlagBits -> Bool $cisSigned :: TypeFlagBits -> Bool bitSize :: TypeFlagBits -> Int $cbitSize :: TypeFlagBits -> Int bitSizeMaybe :: TypeFlagBits -> Maybe Int $cbitSizeMaybe :: TypeFlagBits -> Maybe Int testBit :: TypeFlagBits -> Int -> Bool $ctestBit :: TypeFlagBits -> Int -> Bool complementBit :: TypeFlagBits -> Int -> TypeFlagBits $ccomplementBit :: TypeFlagBits -> Int -> TypeFlagBits clearBit :: TypeFlagBits -> Int -> TypeFlagBits $cclearBit :: TypeFlagBits -> Int -> TypeFlagBits setBit :: TypeFlagBits -> Int -> TypeFlagBits $csetBit :: TypeFlagBits -> Int -> TypeFlagBits bit :: Int -> TypeFlagBits $cbit :: Int -> TypeFlagBits zeroBits :: TypeFlagBits $czeroBits :: TypeFlagBits rotate :: TypeFlagBits -> Int -> TypeFlagBits $crotate :: TypeFlagBits -> Int -> TypeFlagBits shift :: TypeFlagBits -> Int -> TypeFlagBits $cshift :: TypeFlagBits -> Int -> TypeFlagBits complement :: TypeFlagBits -> TypeFlagBits $ccomplement :: TypeFlagBits -> TypeFlagBits xor :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits $cxor :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits .|. :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits $c.|. :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits .&. :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits $c.&. :: TypeFlagBits -> TypeFlagBits -> TypeFlagBits Bits, Bits TypeFlagBits TypeFlagBits -> Int forall b. Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b countTrailingZeros :: TypeFlagBits -> Int $ccountTrailingZeros :: TypeFlagBits -> Int countLeadingZeros :: TypeFlagBits -> Int $ccountLeadingZeros :: TypeFlagBits -> Int finiteBitSize :: TypeFlagBits -> Int $cfiniteBitSize :: TypeFlagBits -> Int FiniteBits) pattern TYPE_FLAG_UNDEFINED :: TypeFlagBits pattern $bTYPE_FLAG_UNDEFINED :: TypeFlagBits $mTYPE_FLAG_UNDEFINED :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_UNDEFINED = TypeFlagBits 0x00000000 pattern TYPE_FLAG_VOID :: TypeFlagBits pattern $bTYPE_FLAG_VOID :: TypeFlagBits $mTYPE_FLAG_VOID :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_VOID = TypeFlagBits 0x00000001 pattern TYPE_FLAG_BOOL :: TypeFlagBits pattern $bTYPE_FLAG_BOOL :: TypeFlagBits $mTYPE_FLAG_BOOL :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_BOOL = TypeFlagBits 0x00000002 pattern TYPE_FLAG_INT :: TypeFlagBits pattern $bTYPE_FLAG_INT :: TypeFlagBits $mTYPE_FLAG_INT :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_INT = TypeFlagBits 0x00000004 pattern TYPE_FLAG_FLOAT :: TypeFlagBits pattern $bTYPE_FLAG_FLOAT :: TypeFlagBits $mTYPE_FLAG_FLOAT :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_FLOAT = TypeFlagBits 0x00000008 pattern TYPE_FLAG_VECTOR :: TypeFlagBits pattern $bTYPE_FLAG_VECTOR :: TypeFlagBits $mTYPE_FLAG_VECTOR :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_VECTOR = TypeFlagBits 0x00000100 pattern TYPE_FLAG_MATRIX :: TypeFlagBits pattern $bTYPE_FLAG_MATRIX :: TypeFlagBits $mTYPE_FLAG_MATRIX :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_MATRIX = TypeFlagBits 0x00000200 pattern TYPE_FLAG_EXTERNAL_IMAGE :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_IMAGE :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_IMAGE :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_IMAGE = TypeFlagBits 0x00010000 pattern TYPE_FLAG_EXTERNAL_SAMPLER :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_SAMPLER :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_SAMPLER :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_SAMPLER = TypeFlagBits 0x00020000 pattern TYPE_FLAG_EXTERNAL_SAMPLED_IMAGE :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_SAMPLED_IMAGE :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_SAMPLED_IMAGE :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_SAMPLED_IMAGE = TypeFlagBits 0x00040000 pattern TYPE_FLAG_EXTERNAL_BLOCK :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_BLOCK :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_BLOCK :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_BLOCK = TypeFlagBits 0x00080000 pattern TYPE_FLAG_EXTERNAL_ACCELERATION_STRUCTURE :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_ACCELERATION_STRUCTURE :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_ACCELERATION_STRUCTURE :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_ACCELERATION_STRUCTURE = TypeFlagBits 0x00100000 pattern TYPE_FLAG_EXTERNAL_MASK :: TypeFlagBits pattern $bTYPE_FLAG_EXTERNAL_MASK :: TypeFlagBits $mTYPE_FLAG_EXTERNAL_MASK :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_EXTERNAL_MASK = TypeFlagBits 0x00FF0000 pattern TYPE_FLAG_STRUCT :: TypeFlagBits pattern $bTYPE_FLAG_STRUCT :: TypeFlagBits $mTYPE_FLAG_STRUCT :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_STRUCT = TypeFlagBits 0x10000000 pattern TYPE_FLAG_ARRAY :: TypeFlagBits pattern $bTYPE_FLAG_ARRAY :: TypeFlagBits $mTYPE_FLAG_ARRAY :: forall {r}. TypeFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r TYPE_FLAG_ARRAY = TypeFlagBits 0x20000000 typeFlagBitNames :: IsString label => [(TypeFlagBits, label)] typeFlagBitNames :: forall label. IsString label => [(TypeFlagBits, label)] typeFlagBitNames = [ (TypeFlagBits TYPE_FLAG_UNDEFINED, label "UNDEFINED") , (TypeFlagBits TYPE_FLAG_VOID, label "VOID") , (TypeFlagBits TYPE_FLAG_BOOL, label "BOOL") , (TypeFlagBits TYPE_FLAG_INT, label "INT") , (TypeFlagBits TYPE_FLAG_FLOAT, label "FLOAT") , (TypeFlagBits TYPE_FLAG_VECTOR, label "VECTOR") , (TypeFlagBits TYPE_FLAG_MATRIX, label "MATRIX") , (TypeFlagBits TYPE_FLAG_EXTERNAL_IMAGE, label "EXTERNAL_IMAGE") , (TypeFlagBits TYPE_FLAG_EXTERNAL_SAMPLER, label "EXTERNAL_SAMPLER") , (TypeFlagBits TYPE_FLAG_EXTERNAL_SAMPLED_IMAGE, label "EXTERNAL_SAMPLED_IMAGE") , (TypeFlagBits TYPE_FLAG_EXTERNAL_BLOCK, label "EXTERNAL_BLOCK") , (TypeFlagBits TYPE_FLAG_EXTERNAL_ACCELERATION_STRUCTURE, label "EXTERNAL_ACCELERATION_STRUCTURE") , (TypeFlagBits TYPE_FLAG_EXTERNAL_MASK, label "EXTERNAL_MASK") , (TypeFlagBits TYPE_FLAG_STRUCT, label "STRUCT") , (TypeFlagBits TYPE_FLAG_ARRAY, label "ARRAY") ] typeFlagsNames :: IsString label => TypeFlags -> [label] typeFlagsNames :: forall label. IsString label => TypeFlagBits -> [label] typeFlagsNames TypeFlagBits bits = do (TypeFlagBits flag, label name) <- forall a. Int -> [a] -> [a] drop Int 1 forall label. IsString label => [(TypeFlagBits, label)] typeFlagBitNames forall (f :: * -> *). Alternative f => Bool -> f () guard forall a b. (a -> b) -> a -> b $ TypeFlagBits bits forall a. Bits a => a -> a -> Bool .&&. TypeFlagBits flag pure label name