{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeSynonymInstances #-}

module Data.SpirV.Enum.ImageOperands where

import Data.Bits (Bits, FiniteBits, (.|.))
import Data.Word (Word32)
import Foreign.Storable (Storable)

type ImageOperands = ImageOperandsBits

newtype ImageOperandsBits = ImageOperandsBits Word32
  deriving newtype (ImageOperandsBits -> ImageOperandsBits -> Bool
(ImageOperandsBits -> ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> ImageOperandsBits -> Bool)
-> Eq ImageOperandsBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImageOperandsBits -> ImageOperandsBits -> Bool
== :: ImageOperandsBits -> ImageOperandsBits -> Bool
$c/= :: ImageOperandsBits -> ImageOperandsBits -> Bool
/= :: ImageOperandsBits -> ImageOperandsBits -> Bool
Eq, Eq ImageOperandsBits
Eq ImageOperandsBits =>
(ImageOperandsBits -> ImageOperandsBits -> Ordering)
-> (ImageOperandsBits -> ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits)
-> (ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits)
-> Ord ImageOperandsBits
ImageOperandsBits -> ImageOperandsBits -> Bool
ImageOperandsBits -> ImageOperandsBits -> Ordering
ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
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 :: ImageOperandsBits -> ImageOperandsBits -> Ordering
compare :: ImageOperandsBits -> ImageOperandsBits -> Ordering
$c< :: ImageOperandsBits -> ImageOperandsBits -> Bool
< :: ImageOperandsBits -> ImageOperandsBits -> Bool
$c<= :: ImageOperandsBits -> ImageOperandsBits -> Bool
<= :: ImageOperandsBits -> ImageOperandsBits -> Bool
$c> :: ImageOperandsBits -> ImageOperandsBits -> Bool
> :: ImageOperandsBits -> ImageOperandsBits -> Bool
$c>= :: ImageOperandsBits -> ImageOperandsBits -> Bool
>= :: ImageOperandsBits -> ImageOperandsBits -> Bool
$cmax :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
max :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
$cmin :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
min :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
Ord, Ptr ImageOperandsBits -> IO ImageOperandsBits
Ptr ImageOperandsBits -> Int -> IO ImageOperandsBits
Ptr ImageOperandsBits -> Int -> ImageOperandsBits -> IO ()
Ptr ImageOperandsBits -> ImageOperandsBits -> IO ()
ImageOperandsBits -> Int
(ImageOperandsBits -> Int)
-> (ImageOperandsBits -> Int)
-> (Ptr ImageOperandsBits -> Int -> IO ImageOperandsBits)
-> (Ptr ImageOperandsBits -> Int -> ImageOperandsBits -> IO ())
-> (forall b. Ptr b -> Int -> IO ImageOperandsBits)
-> (forall b. Ptr b -> Int -> ImageOperandsBits -> IO ())
-> (Ptr ImageOperandsBits -> IO ImageOperandsBits)
-> (Ptr ImageOperandsBits -> ImageOperandsBits -> IO ())
-> Storable ImageOperandsBits
forall b. Ptr b -> Int -> IO ImageOperandsBits
forall b. Ptr b -> Int -> ImageOperandsBits -> 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 :: ImageOperandsBits -> Int
sizeOf :: ImageOperandsBits -> Int
$calignment :: ImageOperandsBits -> Int
alignment :: ImageOperandsBits -> Int
$cpeekElemOff :: Ptr ImageOperandsBits -> Int -> IO ImageOperandsBits
peekElemOff :: Ptr ImageOperandsBits -> Int -> IO ImageOperandsBits
$cpokeElemOff :: Ptr ImageOperandsBits -> Int -> ImageOperandsBits -> IO ()
pokeElemOff :: Ptr ImageOperandsBits -> Int -> ImageOperandsBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ImageOperandsBits
peekByteOff :: forall b. Ptr b -> Int -> IO ImageOperandsBits
$cpokeByteOff :: forall b. Ptr b -> Int -> ImageOperandsBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> ImageOperandsBits -> IO ()
$cpeek :: Ptr ImageOperandsBits -> IO ImageOperandsBits
peek :: Ptr ImageOperandsBits -> IO ImageOperandsBits
$cpoke :: Ptr ImageOperandsBits -> ImageOperandsBits -> IO ()
poke :: Ptr ImageOperandsBits -> ImageOperandsBits -> IO ()
Storable, Eq ImageOperandsBits
ImageOperandsBits
Eq ImageOperandsBits =>
(ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits)
-> (ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits)
-> (ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits)
-> (ImageOperandsBits -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> ImageOperandsBits
-> (Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> Bool)
-> (ImageOperandsBits -> Maybe Int)
-> (ImageOperandsBits -> Int)
-> (ImageOperandsBits -> Bool)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int -> ImageOperandsBits)
-> (ImageOperandsBits -> Int)
-> Bits ImageOperandsBits
Int -> ImageOperandsBits
ImageOperandsBits -> Bool
ImageOperandsBits -> Int
ImageOperandsBits -> Maybe Int
ImageOperandsBits -> ImageOperandsBits
ImageOperandsBits -> Int -> Bool
ImageOperandsBits -> Int -> ImageOperandsBits
ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
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.&. :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
.&. :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
$c.|. :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
.|. :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
$cxor :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
xor :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
$ccomplement :: ImageOperandsBits -> ImageOperandsBits
complement :: ImageOperandsBits -> ImageOperandsBits
$cshift :: ImageOperandsBits -> Int -> ImageOperandsBits
shift :: ImageOperandsBits -> Int -> ImageOperandsBits
$crotate :: ImageOperandsBits -> Int -> ImageOperandsBits
rotate :: ImageOperandsBits -> Int -> ImageOperandsBits
$czeroBits :: ImageOperandsBits
zeroBits :: ImageOperandsBits
$cbit :: Int -> ImageOperandsBits
bit :: Int -> ImageOperandsBits
$csetBit :: ImageOperandsBits -> Int -> ImageOperandsBits
setBit :: ImageOperandsBits -> Int -> ImageOperandsBits
$cclearBit :: ImageOperandsBits -> Int -> ImageOperandsBits
clearBit :: ImageOperandsBits -> Int -> ImageOperandsBits
$ccomplementBit :: ImageOperandsBits -> Int -> ImageOperandsBits
complementBit :: ImageOperandsBits -> Int -> ImageOperandsBits
$ctestBit :: ImageOperandsBits -> Int -> Bool
testBit :: ImageOperandsBits -> Int -> Bool
$cbitSizeMaybe :: ImageOperandsBits -> Maybe Int
bitSizeMaybe :: ImageOperandsBits -> Maybe Int
$cbitSize :: ImageOperandsBits -> Int
bitSize :: ImageOperandsBits -> Int
$cisSigned :: ImageOperandsBits -> Bool
isSigned :: ImageOperandsBits -> Bool
$cshiftL :: ImageOperandsBits -> Int -> ImageOperandsBits
shiftL :: ImageOperandsBits -> Int -> ImageOperandsBits
$cunsafeShiftL :: ImageOperandsBits -> Int -> ImageOperandsBits
unsafeShiftL :: ImageOperandsBits -> Int -> ImageOperandsBits
$cshiftR :: ImageOperandsBits -> Int -> ImageOperandsBits
shiftR :: ImageOperandsBits -> Int -> ImageOperandsBits
$cunsafeShiftR :: ImageOperandsBits -> Int -> ImageOperandsBits
unsafeShiftR :: ImageOperandsBits -> Int -> ImageOperandsBits
$crotateL :: ImageOperandsBits -> Int -> ImageOperandsBits
rotateL :: ImageOperandsBits -> Int -> ImageOperandsBits
$crotateR :: ImageOperandsBits -> Int -> ImageOperandsBits
rotateR :: ImageOperandsBits -> Int -> ImageOperandsBits
$cpopCount :: ImageOperandsBits -> Int
popCount :: ImageOperandsBits -> Int
Bits, Bits ImageOperandsBits
Bits ImageOperandsBits =>
(ImageOperandsBits -> Int)
-> (ImageOperandsBits -> Int)
-> (ImageOperandsBits -> Int)
-> FiniteBits ImageOperandsBits
ImageOperandsBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: ImageOperandsBits -> Int
finiteBitSize :: ImageOperandsBits -> Int
$ccountLeadingZeros :: ImageOperandsBits -> Int
countLeadingZeros :: ImageOperandsBits -> Int
$ccountTrailingZeros :: ImageOperandsBits -> Int
countTrailingZeros :: ImageOperandsBits -> Int
FiniteBits)

instance Semigroup ImageOperands where
  (ImageOperandsBits Word32
a) <> :: ImageOperandsBits -> ImageOperandsBits -> ImageOperandsBits
<> (ImageOperandsBits Word32
b) = Word32 -> ImageOperandsBits
ImageOperandsBits (Word32
a Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
b)

instance Monoid ImageOperands where
  mempty :: ImageOperandsBits
mempty = Word32 -> ImageOperandsBits
ImageOperandsBits Word32
0

pattern Bias :: ImageOperandsBits
pattern $mBias :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bBias :: ImageOperandsBits
Bias = ImageOperandsBits 0x00000001

pattern Lod :: ImageOperandsBits
pattern $mLod :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bLod :: ImageOperandsBits
Lod = ImageOperandsBits 0x00000002

pattern Grad :: ImageOperandsBits
pattern $mGrad :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bGrad :: ImageOperandsBits
Grad = ImageOperandsBits 0x00000004

pattern ConstOffset :: ImageOperandsBits
pattern $mConstOffset :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bConstOffset :: ImageOperandsBits
ConstOffset = ImageOperandsBits 0x00000008

pattern Offset :: ImageOperandsBits
pattern $mOffset :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bOffset :: ImageOperandsBits
Offset = ImageOperandsBits 0x00000010

pattern ConstOffsets :: ImageOperandsBits
pattern $mConstOffsets :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bConstOffsets :: ImageOperandsBits
ConstOffsets = ImageOperandsBits 0x00000020

pattern Sample :: ImageOperandsBits
pattern $mSample :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bSample :: ImageOperandsBits
Sample = ImageOperandsBits 0x00000040

pattern MinLod :: ImageOperandsBits
pattern $mMinLod :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bMinLod :: ImageOperandsBits
MinLod = ImageOperandsBits 0x00000080

pattern MakeTexelAvailable :: ImageOperandsBits
pattern $mMakeTexelAvailable :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bMakeTexelAvailable :: ImageOperandsBits
MakeTexelAvailable = ImageOperandsBits 0x00000100

pattern MakeTexelAvailableKHR :: ImageOperandsBits
pattern $mMakeTexelAvailableKHR :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bMakeTexelAvailableKHR :: ImageOperandsBits
MakeTexelAvailableKHR = ImageOperandsBits 0x00000100

pattern MakeTexelVisible :: ImageOperandsBits
pattern $mMakeTexelVisible :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bMakeTexelVisible :: ImageOperandsBits
MakeTexelVisible = ImageOperandsBits 0x00000200

pattern MakeTexelVisibleKHR :: ImageOperandsBits
pattern $mMakeTexelVisibleKHR :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bMakeTexelVisibleKHR :: ImageOperandsBits
MakeTexelVisibleKHR = ImageOperandsBits 0x00000200

pattern NonPrivateTexel :: ImageOperandsBits
pattern $mNonPrivateTexel :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonPrivateTexel :: ImageOperandsBits
NonPrivateTexel = ImageOperandsBits 0x00000400

pattern NonPrivateTexelKHR :: ImageOperandsBits
pattern $mNonPrivateTexelKHR :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonPrivateTexelKHR :: ImageOperandsBits
NonPrivateTexelKHR = ImageOperandsBits 0x00000400

pattern VolatileTexel :: ImageOperandsBits
pattern $mVolatileTexel :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bVolatileTexel :: ImageOperandsBits
VolatileTexel = ImageOperandsBits 0x00000800

pattern VolatileTexelKHR :: ImageOperandsBits
pattern $mVolatileTexelKHR :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bVolatileTexelKHR :: ImageOperandsBits
VolatileTexelKHR = ImageOperandsBits 0x00000800

pattern SignExtend :: ImageOperandsBits
pattern $mSignExtend :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bSignExtend :: ImageOperandsBits
SignExtend = ImageOperandsBits 0x00001000

pattern ZeroExtend :: ImageOperandsBits
pattern $mZeroExtend :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bZeroExtend :: ImageOperandsBits
ZeroExtend = ImageOperandsBits 0x00002000

pattern Nontemporal :: ImageOperandsBits
pattern $mNontemporal :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bNontemporal :: ImageOperandsBits
Nontemporal = ImageOperandsBits 0x00004000

pattern Offsets :: ImageOperandsBits
pattern $mOffsets :: forall {r}. ImageOperandsBits -> ((# #) -> r) -> ((# #) -> r) -> r
$bOffsets :: ImageOperandsBits
Offsets = ImageOperandsBits 0x00010000