{-# language CPP #-}
module Vulkan.Core10.Enums.EventCreateFlagBits ( EventCreateFlags
, EventCreateFlagBits( EVENT_CREATE_DEVICE_ONLY_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 EventCreateFlags = EventCreateFlagBits
newtype EventCreateFlagBits = EventCreateFlagBits Flags
deriving newtype (EventCreateFlagBits -> EventCreateFlagBits -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c/= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
== :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c== :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
Eq, Eq EventCreateFlagBits
EventCreateFlagBits -> EventCreateFlagBits -> Bool
EventCreateFlagBits -> EventCreateFlagBits -> Ordering
EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
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 :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$cmin :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
max :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$cmax :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
>= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c>= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
> :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c> :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
<= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c<= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
< :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c< :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
compare :: EventCreateFlagBits -> EventCreateFlagBits -> Ordering
$ccompare :: EventCreateFlagBits -> EventCreateFlagBits -> Ordering
Ord, Ptr EventCreateFlagBits -> IO EventCreateFlagBits
Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ()
EventCreateFlagBits -> Int
forall b. Ptr b -> Int -> IO EventCreateFlagBits
forall b. Ptr b -> Int -> EventCreateFlagBits -> 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 EventCreateFlagBits -> EventCreateFlagBits -> IO ()
$cpoke :: Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ()
peek :: Ptr EventCreateFlagBits -> IO EventCreateFlagBits
$cpeek :: Ptr EventCreateFlagBits -> IO EventCreateFlagBits
pokeByteOff :: forall b. Ptr b -> Int -> EventCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> EventCreateFlagBits -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO EventCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO EventCreateFlagBits
pokeElemOff :: Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
peekElemOff :: Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
$cpeekElemOff :: Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
alignment :: EventCreateFlagBits -> Int
$calignment :: EventCreateFlagBits -> Int
sizeOf :: EventCreateFlagBits -> Int
$csizeOf :: EventCreateFlagBits -> Int
Storable, EventCreateFlagBits
forall a. a -> Zero a
zero :: EventCreateFlagBits
$czero :: EventCreateFlagBits
Zero, Eq EventCreateFlagBits
EventCreateFlagBits
Int -> EventCreateFlagBits
EventCreateFlagBits -> Bool
EventCreateFlagBits -> Int
EventCreateFlagBits -> Maybe Int
EventCreateFlagBits -> EventCreateFlagBits
EventCreateFlagBits -> Int -> Bool
EventCreateFlagBits -> Int -> EventCreateFlagBits
EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
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 :: EventCreateFlagBits -> Int
$cpopCount :: EventCreateFlagBits -> Int
rotateR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotateR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
rotateL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotateL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
unsafeShiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cunsafeShiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cshiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
unsafeShiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cunsafeShiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cshiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
isSigned :: EventCreateFlagBits -> Bool
$cisSigned :: EventCreateFlagBits -> Bool
bitSize :: EventCreateFlagBits -> Int
$cbitSize :: EventCreateFlagBits -> Int
bitSizeMaybe :: EventCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: EventCreateFlagBits -> Maybe Int
testBit :: EventCreateFlagBits -> Int -> Bool
$ctestBit :: EventCreateFlagBits -> Int -> Bool
complementBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$ccomplementBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
clearBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cclearBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
setBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$csetBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
bit :: Int -> EventCreateFlagBits
$cbit :: Int -> EventCreateFlagBits
zeroBits :: EventCreateFlagBits
$czeroBits :: EventCreateFlagBits
rotate :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotate :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shift :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cshift :: EventCreateFlagBits -> Int -> EventCreateFlagBits
complement :: EventCreateFlagBits -> EventCreateFlagBits
$ccomplement :: EventCreateFlagBits -> EventCreateFlagBits
xor :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$cxor :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
.|. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$c.|. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
.&. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$c.&. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
Bits, Bits EventCreateFlagBits
EventCreateFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: EventCreateFlagBits -> Int
$ccountTrailingZeros :: EventCreateFlagBits -> Int
countLeadingZeros :: EventCreateFlagBits -> Int
$ccountLeadingZeros :: EventCreateFlagBits -> Int
finiteBitSize :: EventCreateFlagBits -> Int
$cfiniteBitSize :: EventCreateFlagBits -> Int
FiniteBits)
pattern $bEVENT_CREATE_DEVICE_ONLY_BIT :: EventCreateFlagBits
$mEVENT_CREATE_DEVICE_ONLY_BIT :: forall {r}.
EventCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
EVENT_CREATE_DEVICE_ONLY_BIT = EventCreateFlagBits 0x00000001
conNameEventCreateFlagBits :: String
conNameEventCreateFlagBits :: String
conNameEventCreateFlagBits = String
"EventCreateFlagBits"
enumPrefixEventCreateFlagBits :: String
enumPrefixEventCreateFlagBits :: String
enumPrefixEventCreateFlagBits = String
"EVENT_CREATE_DEVICE_ONLY_BIT"
showTableEventCreateFlagBits :: [(EventCreateFlagBits, String)]
showTableEventCreateFlagBits :: [(EventCreateFlagBits, String)]
showTableEventCreateFlagBits = [(EventCreateFlagBits
EVENT_CREATE_DEVICE_ONLY_BIT, String
"")]
instance Show EventCreateFlagBits where
showsPrec :: Int -> EventCreateFlagBits -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixEventCreateFlagBits
[(EventCreateFlagBits, String)]
showTableEventCreateFlagBits
String
conNameEventCreateFlagBits
(\(EventCreateFlagBits 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 EventCreateFlagBits where
readPrec :: ReadPrec EventCreateFlagBits
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixEventCreateFlagBits
[(EventCreateFlagBits, String)]
showTableEventCreateFlagBits
String
conNameEventCreateFlagBits
Flags -> EventCreateFlagBits
EventCreateFlagBits