{-# language CPP #-}
module Vulkan.Core10.Enums.EventCreateFlags  (EventCreateFlags(..)) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
-- | VkEventCreateFlags - Reserved for future use
--
-- = Description
--
-- 'EventCreateFlags' is a bitmask type for setting a mask, but is
-- currently reserved for future use.
--
-- = See Also
--
-- 'Vulkan.Core10.Event.EventCreateInfo'
newtype EventCreateFlags = EventCreateFlags Flags
  deriving newtype (EventCreateFlags -> EventCreateFlags -> Bool
(EventCreateFlags -> EventCreateFlags -> Bool)
-> (EventCreateFlags -> EventCreateFlags -> Bool)
-> Eq EventCreateFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventCreateFlags -> EventCreateFlags -> Bool
$c/= :: EventCreateFlags -> EventCreateFlags -> Bool
== :: EventCreateFlags -> EventCreateFlags -> Bool
$c== :: EventCreateFlags -> EventCreateFlags -> Bool
Eq, Eq EventCreateFlags
Eq EventCreateFlags =>
(EventCreateFlags -> EventCreateFlags -> Ordering)
-> (EventCreateFlags -> EventCreateFlags -> Bool)
-> (EventCreateFlags -> EventCreateFlags -> Bool)
-> (EventCreateFlags -> EventCreateFlags -> Bool)
-> (EventCreateFlags -> EventCreateFlags -> Bool)
-> (EventCreateFlags -> EventCreateFlags -> EventCreateFlags)
-> (EventCreateFlags -> EventCreateFlags -> EventCreateFlags)
-> Ord EventCreateFlags
EventCreateFlags -> EventCreateFlags -> Bool
EventCreateFlags -> EventCreateFlags -> Ordering
EventCreateFlags -> EventCreateFlags -> EventCreateFlags
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 :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$cmin :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
max :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$cmax :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
>= :: EventCreateFlags -> EventCreateFlags -> Bool
$c>= :: EventCreateFlags -> EventCreateFlags -> Bool
> :: EventCreateFlags -> EventCreateFlags -> Bool
$c> :: EventCreateFlags -> EventCreateFlags -> Bool
<= :: EventCreateFlags -> EventCreateFlags -> Bool
$c<= :: EventCreateFlags -> EventCreateFlags -> Bool
< :: EventCreateFlags -> EventCreateFlags -> Bool
$c< :: EventCreateFlags -> EventCreateFlags -> Bool
compare :: EventCreateFlags -> EventCreateFlags -> Ordering
$ccompare :: EventCreateFlags -> EventCreateFlags -> Ordering
$cp1Ord :: Eq EventCreateFlags
Ord, Ptr b -> Int -> IO EventCreateFlags
Ptr b -> Int -> EventCreateFlags -> IO ()
Ptr EventCreateFlags -> IO EventCreateFlags
Ptr EventCreateFlags -> Int -> IO EventCreateFlags
Ptr EventCreateFlags -> Int -> EventCreateFlags -> IO ()
Ptr EventCreateFlags -> EventCreateFlags -> IO ()
EventCreateFlags -> Int
(EventCreateFlags -> Int)
-> (EventCreateFlags -> Int)
-> (Ptr EventCreateFlags -> Int -> IO EventCreateFlags)
-> (Ptr EventCreateFlags -> Int -> EventCreateFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO EventCreateFlags)
-> (forall b. Ptr b -> Int -> EventCreateFlags -> IO ())
-> (Ptr EventCreateFlags -> IO EventCreateFlags)
-> (Ptr EventCreateFlags -> EventCreateFlags -> IO ())
-> Storable EventCreateFlags
forall b. Ptr b -> Int -> IO EventCreateFlags
forall b. Ptr b -> Int -> EventCreateFlags -> 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 EventCreateFlags -> EventCreateFlags -> IO ()
$cpoke :: Ptr EventCreateFlags -> EventCreateFlags -> IO ()
peek :: Ptr EventCreateFlags -> IO EventCreateFlags
$cpeek :: Ptr EventCreateFlags -> IO EventCreateFlags
pokeByteOff :: Ptr b -> Int -> EventCreateFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> EventCreateFlags -> IO ()
peekByteOff :: Ptr b -> Int -> IO EventCreateFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO EventCreateFlags
pokeElemOff :: Ptr EventCreateFlags -> Int -> EventCreateFlags -> IO ()
$cpokeElemOff :: Ptr EventCreateFlags -> Int -> EventCreateFlags -> IO ()
peekElemOff :: Ptr EventCreateFlags -> Int -> IO EventCreateFlags
$cpeekElemOff :: Ptr EventCreateFlags -> Int -> IO EventCreateFlags
alignment :: EventCreateFlags -> Int
$calignment :: EventCreateFlags -> Int
sizeOf :: EventCreateFlags -> Int
$csizeOf :: EventCreateFlags -> Int
Storable, EventCreateFlags
EventCreateFlags -> Zero EventCreateFlags
forall a. a -> Zero a
zero :: EventCreateFlags
$czero :: EventCreateFlags
Zero, Eq EventCreateFlags
EventCreateFlags
Eq EventCreateFlags =>
(EventCreateFlags -> EventCreateFlags -> EventCreateFlags)
-> (EventCreateFlags -> EventCreateFlags -> EventCreateFlags)
-> (EventCreateFlags -> EventCreateFlags -> EventCreateFlags)
-> (EventCreateFlags -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> EventCreateFlags
-> (Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> Bool)
-> (EventCreateFlags -> Maybe Int)
-> (EventCreateFlags -> Int)
-> (EventCreateFlags -> Bool)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int -> EventCreateFlags)
-> (EventCreateFlags -> Int)
-> Bits EventCreateFlags
Int -> EventCreateFlags
EventCreateFlags -> Bool
EventCreateFlags -> Int
EventCreateFlags -> Maybe Int
EventCreateFlags -> EventCreateFlags
EventCreateFlags -> Int -> Bool
EventCreateFlags -> Int -> EventCreateFlags
EventCreateFlags -> EventCreateFlags -> EventCreateFlags
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 :: EventCreateFlags -> Int
$cpopCount :: EventCreateFlags -> Int
rotateR :: EventCreateFlags -> Int -> EventCreateFlags
$crotateR :: EventCreateFlags -> Int -> EventCreateFlags
rotateL :: EventCreateFlags -> Int -> EventCreateFlags
$crotateL :: EventCreateFlags -> Int -> EventCreateFlags
unsafeShiftR :: EventCreateFlags -> Int -> EventCreateFlags
$cunsafeShiftR :: EventCreateFlags -> Int -> EventCreateFlags
shiftR :: EventCreateFlags -> Int -> EventCreateFlags
$cshiftR :: EventCreateFlags -> Int -> EventCreateFlags
unsafeShiftL :: EventCreateFlags -> Int -> EventCreateFlags
$cunsafeShiftL :: EventCreateFlags -> Int -> EventCreateFlags
shiftL :: EventCreateFlags -> Int -> EventCreateFlags
$cshiftL :: EventCreateFlags -> Int -> EventCreateFlags
isSigned :: EventCreateFlags -> Bool
$cisSigned :: EventCreateFlags -> Bool
bitSize :: EventCreateFlags -> Int
$cbitSize :: EventCreateFlags -> Int
bitSizeMaybe :: EventCreateFlags -> Maybe Int
$cbitSizeMaybe :: EventCreateFlags -> Maybe Int
testBit :: EventCreateFlags -> Int -> Bool
$ctestBit :: EventCreateFlags -> Int -> Bool
complementBit :: EventCreateFlags -> Int -> EventCreateFlags
$ccomplementBit :: EventCreateFlags -> Int -> EventCreateFlags
clearBit :: EventCreateFlags -> Int -> EventCreateFlags
$cclearBit :: EventCreateFlags -> Int -> EventCreateFlags
setBit :: EventCreateFlags -> Int -> EventCreateFlags
$csetBit :: EventCreateFlags -> Int -> EventCreateFlags
bit :: Int -> EventCreateFlags
$cbit :: Int -> EventCreateFlags
zeroBits :: EventCreateFlags
$czeroBits :: EventCreateFlags
rotate :: EventCreateFlags -> Int -> EventCreateFlags
$crotate :: EventCreateFlags -> Int -> EventCreateFlags
shift :: EventCreateFlags -> Int -> EventCreateFlags
$cshift :: EventCreateFlags -> Int -> EventCreateFlags
complement :: EventCreateFlags -> EventCreateFlags
$ccomplement :: EventCreateFlags -> EventCreateFlags
xor :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$cxor :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
.|. :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$c.|. :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
.&. :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$c.&. :: EventCreateFlags -> EventCreateFlags -> EventCreateFlags
$cp1Bits :: Eq EventCreateFlags
Bits)



instance Show EventCreateFlags where
  showsPrec :: Int -> EventCreateFlags -> ShowS
showsPrec p :: Int
p = \case
    EventCreateFlags x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "EventCreateFlags 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read EventCreateFlags where
  readPrec :: ReadPrec EventCreateFlags
readPrec = ReadPrec EventCreateFlags -> ReadPrec EventCreateFlags
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec EventCreateFlags)] -> ReadPrec EventCreateFlags
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose []
                     ReadPrec EventCreateFlags
-> ReadPrec EventCreateFlags -> ReadPrec EventCreateFlags
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec EventCreateFlags -> ReadPrec EventCreateFlags
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "EventCreateFlags")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       EventCreateFlags -> ReadPrec EventCreateFlags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> EventCreateFlags
EventCreateFlags Flags
v)))