{-# language CPP #-}
-- No documentation found for Chapter "EventCreateFlagBits"
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

-- | VkEventCreateFlagBits - Event creation flag bits
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'EventCreateFlags'
newtype EventCreateFlagBits = EventCreateFlagBits Flags
  deriving newtype (EventCreateFlagBits -> EventCreateFlagBits -> Bool
(EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> Eq EventCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
== :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$c/= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
/= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
Eq, Eq EventCreateFlagBits
Eq EventCreateFlagBits =>
(EventCreateFlagBits -> EventCreateFlagBits -> Ordering)
-> (EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits -> EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits
    -> EventCreateFlagBits -> EventCreateFlagBits)
-> (EventCreateFlagBits
    -> EventCreateFlagBits -> EventCreateFlagBits)
-> Ord 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
$ccompare :: EventCreateFlagBits -> EventCreateFlagBits -> Ordering
compare :: EventCreateFlagBits -> EventCreateFlagBits -> Ordering
$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
>= :: EventCreateFlagBits -> EventCreateFlagBits -> Bool
$cmax :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
max :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$cmin :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
min :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
Ord, Ptr EventCreateFlagBits -> IO EventCreateFlagBits
Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ()
EventCreateFlagBits -> Int
(EventCreateFlagBits -> Int)
-> (EventCreateFlagBits -> Int)
-> (Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits)
-> (Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO EventCreateFlagBits)
-> (forall b. Ptr b -> Int -> EventCreateFlagBits -> IO ())
-> (Ptr EventCreateFlagBits -> IO EventCreateFlagBits)
-> (Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ())
-> Storable EventCreateFlagBits
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
$csizeOf :: EventCreateFlagBits -> Int
sizeOf :: EventCreateFlagBits -> Int
$calignment :: EventCreateFlagBits -> Int
alignment :: EventCreateFlagBits -> Int
$cpeekElemOff :: Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
peekElemOff :: Ptr EventCreateFlagBits -> Int -> IO EventCreateFlagBits
$cpokeElemOff :: Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
pokeElemOff :: Ptr EventCreateFlagBits -> Int -> EventCreateFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO EventCreateFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO EventCreateFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> EventCreateFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> EventCreateFlagBits -> IO ()
$cpeek :: Ptr EventCreateFlagBits -> IO EventCreateFlagBits
peek :: Ptr EventCreateFlagBits -> IO EventCreateFlagBits
$cpoke :: Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ()
poke :: Ptr EventCreateFlagBits -> EventCreateFlagBits -> IO ()
Storable, EventCreateFlagBits
EventCreateFlagBits -> Zero EventCreateFlagBits
forall a. a -> Zero a
$czero :: EventCreateFlagBits
zero :: EventCreateFlagBits
Zero, Eq EventCreateFlagBits
EventCreateFlagBits
Eq EventCreateFlagBits =>
(EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits)
-> (EventCreateFlagBits
    -> EventCreateFlagBits -> EventCreateFlagBits)
-> (EventCreateFlagBits
    -> EventCreateFlagBits -> EventCreateFlagBits)
-> (EventCreateFlagBits -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> EventCreateFlagBits
-> (Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> Bool)
-> (EventCreateFlagBits -> Maybe Int)
-> (EventCreateFlagBits -> Int)
-> (EventCreateFlagBits -> Bool)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int -> EventCreateFlagBits)
-> (EventCreateFlagBits -> Int)
-> Bits 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
$c.&. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
.&. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$c.|. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
.|. :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$cxor :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
xor :: EventCreateFlagBits -> EventCreateFlagBits -> EventCreateFlagBits
$ccomplement :: EventCreateFlagBits -> EventCreateFlagBits
complement :: EventCreateFlagBits -> EventCreateFlagBits
$cshift :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shift :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotate :: EventCreateFlagBits -> Int -> EventCreateFlagBits
rotate :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$czeroBits :: EventCreateFlagBits
zeroBits :: EventCreateFlagBits
$cbit :: Int -> EventCreateFlagBits
bit :: Int -> EventCreateFlagBits
$csetBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
setBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cclearBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
clearBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$ccomplementBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
complementBit :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$ctestBit :: EventCreateFlagBits -> Int -> Bool
testBit :: EventCreateFlagBits -> Int -> Bool
$cbitSizeMaybe :: EventCreateFlagBits -> Maybe Int
bitSizeMaybe :: EventCreateFlagBits -> Maybe Int
$cbitSize :: EventCreateFlagBits -> Int
bitSize :: EventCreateFlagBits -> Int
$cisSigned :: EventCreateFlagBits -> Bool
isSigned :: EventCreateFlagBits -> Bool
$cshiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cunsafeShiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
unsafeShiftL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cshiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
shiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cunsafeShiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
unsafeShiftR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotateL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
rotateL :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$crotateR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
rotateR :: EventCreateFlagBits -> Int -> EventCreateFlagBits
$cpopCount :: EventCreateFlagBits -> Int
popCount :: EventCreateFlagBits -> Int
Bits, Bits EventCreateFlagBits
Bits EventCreateFlagBits =>
(EventCreateFlagBits -> Int)
-> (EventCreateFlagBits -> Int)
-> (EventCreateFlagBits -> Int)
-> FiniteBits EventCreateFlagBits
EventCreateFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: EventCreateFlagBits -> Int
finiteBitSize :: EventCreateFlagBits -> Int
$ccountLeadingZeros :: EventCreateFlagBits -> Int
countLeadingZeros :: EventCreateFlagBits -> Int
$ccountTrailingZeros :: EventCreateFlagBits -> Int
countTrailingZeros :: EventCreateFlagBits -> Int
FiniteBits)

-- | 'EVENT_CREATE_DEVICE_ONLY_BIT' specifies that host event commands will
-- not be used with this event.
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 =
    String
-> [(EventCreateFlagBits, String)]
-> String
-> (EventCreateFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> EventCreateFlagBits
-> ShowS
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" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. Integral a => a -> ShowS
showHex Flags
x)

instance Read EventCreateFlagBits where
  readPrec :: ReadPrec EventCreateFlagBits
readPrec =
    String
-> [(EventCreateFlagBits, String)]
-> String
-> (Flags -> EventCreateFlagBits)
-> ReadPrec EventCreateFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixEventCreateFlagBits
      [(EventCreateFlagBits, String)]
showTableEventCreateFlagBits
      String
conNameEventCreateFlagBits
      Flags -> EventCreateFlagBits
EventCreateFlagBits