{-# language CPP #-}
module Vulkan.Core10.Enums.DependencyFlagBits  ( DependencyFlags
                                               , DependencyFlagBits( DEPENDENCY_BY_REGION_BIT
                                                                   , DEPENDENCY_FEEDBACK_LOOP_BIT_EXT
                                                                   , DEPENDENCY_VIEW_LOCAL_BIT
                                                                   , DEPENDENCY_DEVICE_GROUP_BIT
                                                                   , ..
                                                                   )
                                               ) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
type DependencyFlags = DependencyFlagBits
newtype DependencyFlagBits = DependencyFlagBits Flags
  deriving newtype (DependencyFlagBits -> DependencyFlagBits -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c/= :: DependencyFlagBits -> DependencyFlagBits -> Bool
== :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c== :: DependencyFlagBits -> DependencyFlagBits -> Bool
Eq, Eq DependencyFlagBits
DependencyFlagBits -> DependencyFlagBits -> Bool
DependencyFlagBits -> DependencyFlagBits -> Ordering
DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
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 :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
$cmin :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
max :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
$cmax :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
>= :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c>= :: DependencyFlagBits -> DependencyFlagBits -> Bool
> :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c> :: DependencyFlagBits -> DependencyFlagBits -> Bool
<= :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c<= :: DependencyFlagBits -> DependencyFlagBits -> Bool
< :: DependencyFlagBits -> DependencyFlagBits -> Bool
$c< :: DependencyFlagBits -> DependencyFlagBits -> Bool
compare :: DependencyFlagBits -> DependencyFlagBits -> Ordering
$ccompare :: DependencyFlagBits -> DependencyFlagBits -> Ordering
Ord, Ptr DependencyFlagBits -> IO DependencyFlagBits
Ptr DependencyFlagBits -> Int -> IO DependencyFlagBits
Ptr DependencyFlagBits -> Int -> DependencyFlagBits -> IO ()
Ptr DependencyFlagBits -> DependencyFlagBits -> IO ()
DependencyFlagBits -> Int
forall b. Ptr b -> Int -> IO DependencyFlagBits
forall b. Ptr b -> Int -> DependencyFlagBits -> 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
poke :: Ptr DependencyFlagBits -> DependencyFlagBits -> IO ()
$cpoke :: Ptr DependencyFlagBits -> DependencyFlagBits -> IO ()
peek :: Ptr DependencyFlagBits -> IO DependencyFlagBits
$cpeek :: Ptr DependencyFlagBits -> IO DependencyFlagBits
pokeByteOff :: forall b. Ptr b -> Int -> DependencyFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DependencyFlagBits -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DependencyFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DependencyFlagBits
pokeElemOff :: Ptr DependencyFlagBits -> Int -> DependencyFlagBits -> IO ()
$cpokeElemOff :: Ptr DependencyFlagBits -> Int -> DependencyFlagBits -> IO ()
peekElemOff :: Ptr DependencyFlagBits -> Int -> IO DependencyFlagBits
$cpeekElemOff :: Ptr DependencyFlagBits -> Int -> IO DependencyFlagBits
alignment :: DependencyFlagBits -> Int
$calignment :: DependencyFlagBits -> Int
sizeOf :: DependencyFlagBits -> Int
$csizeOf :: DependencyFlagBits -> Int
Storable, DependencyFlagBits
forall a. a -> Zero a
zero :: DependencyFlagBits
$czero :: DependencyFlagBits
Zero, Eq DependencyFlagBits
DependencyFlagBits
Int -> DependencyFlagBits
DependencyFlagBits -> Bool
DependencyFlagBits -> Int
DependencyFlagBits -> Maybe Int
DependencyFlagBits -> DependencyFlagBits
DependencyFlagBits -> Int -> Bool
DependencyFlagBits -> Int -> DependencyFlagBits
DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
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 :: DependencyFlagBits -> Int
$cpopCount :: DependencyFlagBits -> Int
rotateR :: DependencyFlagBits -> Int -> DependencyFlagBits
$crotateR :: DependencyFlagBits -> Int -> DependencyFlagBits
rotateL :: DependencyFlagBits -> Int -> DependencyFlagBits
$crotateL :: DependencyFlagBits -> Int -> DependencyFlagBits
unsafeShiftR :: DependencyFlagBits -> Int -> DependencyFlagBits
$cunsafeShiftR :: DependencyFlagBits -> Int -> DependencyFlagBits
shiftR :: DependencyFlagBits -> Int -> DependencyFlagBits
$cshiftR :: DependencyFlagBits -> Int -> DependencyFlagBits
unsafeShiftL :: DependencyFlagBits -> Int -> DependencyFlagBits
$cunsafeShiftL :: DependencyFlagBits -> Int -> DependencyFlagBits
shiftL :: DependencyFlagBits -> Int -> DependencyFlagBits
$cshiftL :: DependencyFlagBits -> Int -> DependencyFlagBits
isSigned :: DependencyFlagBits -> Bool
$cisSigned :: DependencyFlagBits -> Bool
bitSize :: DependencyFlagBits -> Int
$cbitSize :: DependencyFlagBits -> Int
bitSizeMaybe :: DependencyFlagBits -> Maybe Int
$cbitSizeMaybe :: DependencyFlagBits -> Maybe Int
testBit :: DependencyFlagBits -> Int -> Bool
$ctestBit :: DependencyFlagBits -> Int -> Bool
complementBit :: DependencyFlagBits -> Int -> DependencyFlagBits
$ccomplementBit :: DependencyFlagBits -> Int -> DependencyFlagBits
clearBit :: DependencyFlagBits -> Int -> DependencyFlagBits
$cclearBit :: DependencyFlagBits -> Int -> DependencyFlagBits
setBit :: DependencyFlagBits -> Int -> DependencyFlagBits
$csetBit :: DependencyFlagBits -> Int -> DependencyFlagBits
bit :: Int -> DependencyFlagBits
$cbit :: Int -> DependencyFlagBits
zeroBits :: DependencyFlagBits
$czeroBits :: DependencyFlagBits
rotate :: DependencyFlagBits -> Int -> DependencyFlagBits
$crotate :: DependencyFlagBits -> Int -> DependencyFlagBits
shift :: DependencyFlagBits -> Int -> DependencyFlagBits
$cshift :: DependencyFlagBits -> Int -> DependencyFlagBits
complement :: DependencyFlagBits -> DependencyFlagBits
$ccomplement :: DependencyFlagBits -> DependencyFlagBits
xor :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
$cxor :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
.|. :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
$c.|. :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
.&. :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
$c.&. :: DependencyFlagBits -> DependencyFlagBits -> DependencyFlagBits
Bits, Bits DependencyFlagBits
DependencyFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: DependencyFlagBits -> Int
$ccountTrailingZeros :: DependencyFlagBits -> Int
countLeadingZeros :: DependencyFlagBits -> Int
$ccountLeadingZeros :: DependencyFlagBits -> Int
finiteBitSize :: DependencyFlagBits -> Int
$cfiniteBitSize :: DependencyFlagBits -> Int
FiniteBits)
pattern $bDEPENDENCY_BY_REGION_BIT :: DependencyFlagBits
$mDEPENDENCY_BY_REGION_BIT :: forall {r}. DependencyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
DEPENDENCY_BY_REGION_BIT = DependencyFlagBits 0x00000001
pattern $bDEPENDENCY_FEEDBACK_LOOP_BIT_EXT :: DependencyFlagBits
$mDEPENDENCY_FEEDBACK_LOOP_BIT_EXT :: forall {r}. DependencyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
DEPENDENCY_FEEDBACK_LOOP_BIT_EXT = DependencyFlagBits 0x00000008
pattern $bDEPENDENCY_VIEW_LOCAL_BIT :: DependencyFlagBits
$mDEPENDENCY_VIEW_LOCAL_BIT :: forall {r}. DependencyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
DEPENDENCY_VIEW_LOCAL_BIT = DependencyFlagBits 0x00000002
pattern $bDEPENDENCY_DEVICE_GROUP_BIT :: DependencyFlagBits
$mDEPENDENCY_DEVICE_GROUP_BIT :: forall {r}. DependencyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
DEPENDENCY_DEVICE_GROUP_BIT = DependencyFlagBits 0x00000004
conNameDependencyFlagBits :: String
conNameDependencyFlagBits :: String
conNameDependencyFlagBits = String
"DependencyFlagBits"
enumPrefixDependencyFlagBits :: String
enumPrefixDependencyFlagBits :: String
enumPrefixDependencyFlagBits = String
"DEPENDENCY_"
showTableDependencyFlagBits :: [(DependencyFlagBits, String)]
showTableDependencyFlagBits :: [(DependencyFlagBits, String)]
showTableDependencyFlagBits =
  [ (DependencyFlagBits
DEPENDENCY_BY_REGION_BIT, String
"BY_REGION_BIT")
  ,
    ( DependencyFlagBits
DEPENDENCY_FEEDBACK_LOOP_BIT_EXT
    , String
"FEEDBACK_LOOP_BIT_EXT"
    )
  , (DependencyFlagBits
DEPENDENCY_VIEW_LOCAL_BIT, String
"VIEW_LOCAL_BIT")
  ,
    ( DependencyFlagBits
DEPENDENCY_DEVICE_GROUP_BIT
    , String
"DEVICE_GROUP_BIT"
    )
  ]
instance Show DependencyFlagBits where
  showsPrec :: Int -> DependencyFlagBits -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixDependencyFlagBits
      [(DependencyFlagBits, String)]
showTableDependencyFlagBits
      String
conNameDependencyFlagBits
      (\(DependencyFlagBits Flags
x) -> Flags
x)
      (\Flags
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read DependencyFlagBits where
  readPrec :: ReadPrec DependencyFlagBits
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixDependencyFlagBits
      [(DependencyFlagBits, String)]
showTableDependencyFlagBits
      String
conNameDependencyFlagBits
      Flags -> DependencyFlagBits
DependencyFlagBits