{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Semaphore
       (VkSemaphoreImportFlagBitsKHR(..),
        VkSemaphoreImportBitmask(VkSemaphoreImportBitmask,
                                 VkSemaphoreImportFlags, VkSemaphoreImportFlagBits,
                                 VK_SEMAPHORE_IMPORT_TEMPORARY_BIT),
        VkSemaphoreImportFlags, VkSemaphoreImportFlagBits,
        VkSemaphoreType(VkSemaphoreType, VK_SEMAPHORE_TYPE_BINARY,
                        VK_SEMAPHORE_TYPE_TIMELINE),
        VkSemaphoreTypeKHR(..), VkSemaphoreWaitFlagBitsKHR(..),
        VkSemaphoreWaitBitmask(VkSemaphoreWaitBitmask,
                               VkSemaphoreWaitFlags, VkSemaphoreWaitFlagBits,
                               VK_SEMAPHORE_WAIT_ANY_BIT),
        VkSemaphoreWaitFlags, VkSemaphoreWaitFlagBits)
       where
import Data.Bits                       (Bits, FiniteBits)
import Data.Coerce                     (coerce)
import Foreign.Storable                (Storable)
import GHC.Read                        (choose, expectP)
import Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType, Int32)
import Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import Text.ParserCombinators.ReadPrec (prec, step, (+++))
import Text.Read                       (Read (..), parens)
import Text.Read.Lex                   (Lexeme (..))

newtype VkSemaphoreImportFlagBitsKHR = VkSemaphoreImportFlagBitsKHR VkFlags
                                       deriving (VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
(VkSemaphoreImportFlagBitsKHR
 -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> Eq VkSemaphoreImportFlagBitsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c/= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
== :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c== :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
Eq, Eq VkSemaphoreImportFlagBitsKHR
Eq VkSemaphoreImportFlagBitsKHR
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Ordering)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> Ord VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Ordering
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
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 :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$cmin :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
max :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$cmax :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
>= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c>= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
> :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c> :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
<= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c<= :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
< :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
$c< :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Bool
compare :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Ordering
$ccompare :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> Ordering
Ord, Int -> VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR -> Int
VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> [VkSemaphoreImportFlagBitsKHR]
(VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> (VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR])
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR])
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR])
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR
    -> [VkSemaphoreImportFlagBitsKHR])
-> Enum VkSemaphoreImportFlagBitsKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> [VkSemaphoreImportFlagBitsKHR]
$cenumFromThenTo :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR
-> [VkSemaphoreImportFlagBitsKHR]
enumFromTo :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
$cenumFromTo :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
enumFromThen :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
$cenumFromThen :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
enumFrom :: VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
$cenumFrom :: VkSemaphoreImportFlagBitsKHR -> [VkSemaphoreImportFlagBitsKHR]
fromEnum :: VkSemaphoreImportFlagBitsKHR -> Int
$cfromEnum :: VkSemaphoreImportFlagBitsKHR -> Int
toEnum :: Int -> VkSemaphoreImportFlagBitsKHR
$ctoEnum :: Int -> VkSemaphoreImportFlagBitsKHR
pred :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$cpred :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
succ :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$csucc :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
Enum, Eq VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR
Eq VkSemaphoreImportFlagBitsKHR
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> VkSemaphoreImportFlagBitsKHR
-> (Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR -> Int -> Bool)
-> (VkSemaphoreImportFlagBitsKHR -> Maybe Int)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> (VkSemaphoreImportFlagBitsKHR -> Bool)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> Bits VkSemaphoreImportFlagBitsKHR
Int -> VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR -> Bool
VkSemaphoreImportFlagBitsKHR -> Int
VkSemaphoreImportFlagBitsKHR -> Maybe Int
VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR -> Int -> Bool
VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
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 :: VkSemaphoreImportFlagBitsKHR -> Int
$cpopCount :: VkSemaphoreImportFlagBitsKHR -> Int
rotateR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$crotateR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
rotateL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$crotateL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
unsafeShiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cunsafeShiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
shiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cshiftR :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
unsafeShiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cunsafeShiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
shiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cshiftL :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
isSigned :: VkSemaphoreImportFlagBitsKHR -> Bool
$cisSigned :: VkSemaphoreImportFlagBitsKHR -> Bool
bitSize :: VkSemaphoreImportFlagBitsKHR -> Int
$cbitSize :: VkSemaphoreImportFlagBitsKHR -> Int
bitSizeMaybe :: VkSemaphoreImportFlagBitsKHR -> Maybe Int
$cbitSizeMaybe :: VkSemaphoreImportFlagBitsKHR -> Maybe Int
testBit :: VkSemaphoreImportFlagBitsKHR -> Int -> Bool
$ctestBit :: VkSemaphoreImportFlagBitsKHR -> Int -> Bool
complementBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$ccomplementBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
clearBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cclearBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
setBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$csetBit :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
bit :: Int -> VkSemaphoreImportFlagBitsKHR
$cbit :: Int -> VkSemaphoreImportFlagBitsKHR
zeroBits :: VkSemaphoreImportFlagBitsKHR
$czeroBits :: VkSemaphoreImportFlagBitsKHR
rotate :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$crotate :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
shift :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
$cshift :: VkSemaphoreImportFlagBitsKHR -> Int -> VkSemaphoreImportFlagBitsKHR
complement :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$ccomplement :: VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
xor :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$cxor :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
.|. :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$c.|. :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
.&. :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
$c.&. :: VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> VkSemaphoreImportFlagBitsKHR
Bits, Bits VkSemaphoreImportFlagBitsKHR
Bits VkSemaphoreImportFlagBitsKHR
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> FiniteBits VkSemaphoreImportFlagBitsKHR
VkSemaphoreImportFlagBitsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkSemaphoreImportFlagBitsKHR -> Int
$ccountTrailingZeros :: VkSemaphoreImportFlagBitsKHR -> Int
countLeadingZeros :: VkSemaphoreImportFlagBitsKHR -> Int
$ccountLeadingZeros :: VkSemaphoreImportFlagBitsKHR -> Int
finiteBitSize :: VkSemaphoreImportFlagBitsKHR -> Int
$cfiniteBitSize :: VkSemaphoreImportFlagBitsKHR -> Int
FiniteBits, Ptr VkSemaphoreImportFlagBitsKHR -> IO VkSemaphoreImportFlagBitsKHR
Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> IO VkSemaphoreImportFlagBitsKHR
Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> VkSemaphoreImportFlagBitsKHR -> IO ()
Ptr VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> IO ()
VkSemaphoreImportFlagBitsKHR -> Int
(VkSemaphoreImportFlagBitsKHR -> Int)
-> (VkSemaphoreImportFlagBitsKHR -> Int)
-> (Ptr VkSemaphoreImportFlagBitsKHR
    -> Int -> IO VkSemaphoreImportFlagBitsKHR)
-> (Ptr VkSemaphoreImportFlagBitsKHR
    -> Int -> VkSemaphoreImportFlagBitsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkSemaphoreImportFlagBitsKHR)
-> (forall b.
    Ptr b -> Int -> VkSemaphoreImportFlagBitsKHR -> IO ())
-> (Ptr VkSemaphoreImportFlagBitsKHR
    -> IO VkSemaphoreImportFlagBitsKHR)
-> (Ptr VkSemaphoreImportFlagBitsKHR
    -> VkSemaphoreImportFlagBitsKHR -> IO ())
-> Storable VkSemaphoreImportFlagBitsKHR
forall b. Ptr b -> Int -> IO VkSemaphoreImportFlagBitsKHR
forall b. Ptr b -> Int -> VkSemaphoreImportFlagBitsKHR -> 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 VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> IO ()
$cpoke :: Ptr VkSemaphoreImportFlagBitsKHR
-> VkSemaphoreImportFlagBitsKHR -> IO ()
peek :: Ptr VkSemaphoreImportFlagBitsKHR -> IO VkSemaphoreImportFlagBitsKHR
$cpeek :: Ptr VkSemaphoreImportFlagBitsKHR -> IO VkSemaphoreImportFlagBitsKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreImportFlagBitsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreImportFlagBitsKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreImportFlagBitsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreImportFlagBitsKHR
pokeElemOff :: Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> VkSemaphoreImportFlagBitsKHR -> IO ()
$cpokeElemOff :: Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> VkSemaphoreImportFlagBitsKHR -> IO ()
peekElemOff :: Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> IO VkSemaphoreImportFlagBitsKHR
$cpeekElemOff :: Ptr VkSemaphoreImportFlagBitsKHR
-> Int -> IO VkSemaphoreImportFlagBitsKHR
alignment :: VkSemaphoreImportFlagBitsKHR -> Int
$calignment :: VkSemaphoreImportFlagBitsKHR -> Int
sizeOf :: VkSemaphoreImportFlagBitsKHR -> Int
$csizeOf :: VkSemaphoreImportFlagBitsKHR -> Int
Storable)

instance Show VkSemaphoreImportFlagBitsKHR where
    {-# INLINE showsPrec #-}
    showsPrec :: Int -> VkSemaphoreImportFlagBitsKHR -> ShowS
showsPrec = (Int -> VkFlags -> ShowS)
-> Int -> VkSemaphoreImportFlagBitsKHR -> ShowS
coerce (Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec :: Int -> VkFlags -> ShowS)

instance Read VkSemaphoreImportFlagBitsKHR where
    {-# INLINE readsPrec #-}
    readsPrec :: Int -> ReadS VkSemaphoreImportFlagBitsKHR
readsPrec = (Int -> ReadS VkFlags) -> Int -> ReadS VkSemaphoreImportFlagBitsKHR
coerce (Int -> ReadS VkFlags
forall a. Read a => Int -> ReadS a
readsPrec :: Int -> ReadS VkFlags)

newtype VkSemaphoreImportBitmask (a ::
                                    FlagType) = VkSemaphoreImportBitmask VkFlags
                                                deriving (VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
(VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Bool)
-> Eq (VkSemaphoreImportBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
/= :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
== :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
Eq, Eq (VkSemaphoreImportBitmask a)
Eq (VkSemaphoreImportBitmask a)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Ordering)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Bool)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Bool)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Bool)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> Bool)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a)
-> (VkSemaphoreImportBitmask a
    -> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a)
-> Ord (VkSemaphoreImportBitmask a)
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> Ordering
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
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
forall (a :: FlagType). Eq (VkSemaphoreImportBitmask a)
forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
forall (a :: FlagType).
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> Ordering
forall (a :: FlagType).
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
min :: VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
$cmin :: forall (a :: FlagType).
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
max :: VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
$cmax :: forall (a :: FlagType).
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a
>= :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
> :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
<= :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
< :: VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkSemaphoreImportBitmask a -> VkSemaphoreImportBitmask a -> Bool
compare :: VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkSemaphoreImportBitmask a
-> VkSemaphoreImportBitmask a -> Ordering
Ord, Ptr (VkSemaphoreImportBitmask a) -> IO (VkSemaphoreImportBitmask a)
Ptr (VkSemaphoreImportBitmask a)
-> Int -> IO (VkSemaphoreImportBitmask a)
Ptr (VkSemaphoreImportBitmask a)
-> Int -> VkSemaphoreImportBitmask a -> IO ()
Ptr (VkSemaphoreImportBitmask a)
-> VkSemaphoreImportBitmask a -> IO ()
VkSemaphoreImportBitmask a -> Int
(VkSemaphoreImportBitmask a -> Int)
-> (VkSemaphoreImportBitmask a -> Int)
-> (Ptr (VkSemaphoreImportBitmask a)
    -> Int -> IO (VkSemaphoreImportBitmask a))
-> (Ptr (VkSemaphoreImportBitmask a)
    -> Int -> VkSemaphoreImportBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkSemaphoreImportBitmask a))
-> (forall b. Ptr b -> Int -> VkSemaphoreImportBitmask a -> IO ())
-> (Ptr (VkSemaphoreImportBitmask a)
    -> IO (VkSemaphoreImportBitmask a))
-> (Ptr (VkSemaphoreImportBitmask a)
    -> VkSemaphoreImportBitmask a -> IO ())
-> Storable (VkSemaphoreImportBitmask a)
forall b. Ptr b -> Int -> IO (VkSemaphoreImportBitmask a)
forall b. Ptr b -> Int -> VkSemaphoreImportBitmask a -> 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
forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a) -> IO (VkSemaphoreImportBitmask a)
forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> Int -> IO (VkSemaphoreImportBitmask a)
forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> Int -> VkSemaphoreImportBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> VkSemaphoreImportBitmask a -> IO ()
forall (a :: FlagType). VkSemaphoreImportBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSemaphoreImportBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkSemaphoreImportBitmask a -> IO ()
poke :: Ptr (VkSemaphoreImportBitmask a)
-> VkSemaphoreImportBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> VkSemaphoreImportBitmask a -> IO ()
peek :: Ptr (VkSemaphoreImportBitmask a) -> IO (VkSemaphoreImportBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a) -> IO (VkSemaphoreImportBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreImportBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkSemaphoreImportBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkSemaphoreImportBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSemaphoreImportBitmask a)
pokeElemOff :: Ptr (VkSemaphoreImportBitmask a)
-> Int -> VkSemaphoreImportBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> Int -> VkSemaphoreImportBitmask a -> IO ()
peekElemOff :: Ptr (VkSemaphoreImportBitmask a)
-> Int -> IO (VkSemaphoreImportBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkSemaphoreImportBitmask a)
-> Int -> IO (VkSemaphoreImportBitmask a)
alignment :: VkSemaphoreImportBitmask a -> Int
$calignment :: forall (a :: FlagType). VkSemaphoreImportBitmask a -> Int
sizeOf :: VkSemaphoreImportBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkSemaphoreImportBitmask a -> Int
Storable)

type VkSemaphoreImportFlags = VkSemaphoreImportBitmask FlagMask

type VkSemaphoreImportFlagBits = VkSemaphoreImportBitmask FlagBit

pattern VkSemaphoreImportFlagBits ::
        VkFlags -> VkSemaphoreImportBitmask FlagBit

pattern $bVkSemaphoreImportFlagBits :: VkFlags -> VkSemaphoreImportBitmask FlagBit
$mVkSemaphoreImportFlagBits :: forall {r}.
VkSemaphoreImportBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSemaphoreImportFlagBits n = VkSemaphoreImportBitmask n

pattern VkSemaphoreImportFlags ::
        VkFlags -> VkSemaphoreImportBitmask FlagMask

pattern $bVkSemaphoreImportFlags :: VkFlags -> VkSemaphoreImportBitmask FlagMask
$mVkSemaphoreImportFlags :: forall {r}.
VkSemaphoreImportBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSemaphoreImportFlags n = VkSemaphoreImportBitmask n

deriving instance Bits (VkSemaphoreImportBitmask FlagMask)

deriving instance FiniteBits (VkSemaphoreImportBitmask FlagMask)

instance Show (VkSemaphoreImportBitmask a) where
    showsPrec :: Int -> VkSemaphoreImportBitmask a -> ShowS
showsPrec Int
_ VkSemaphoreImportBitmask a
VK_SEMAPHORE_IMPORT_TEMPORARY_BIT
      = String -> ShowS
showString String
"VK_SEMAPHORE_IMPORT_TEMPORARY_BIT"
    showsPrec Int
p (VkSemaphoreImportBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkSemaphoreImportBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkSemaphoreImportBitmask a) where
    readPrec :: ReadPrec (VkSemaphoreImportBitmask a)
readPrec
      = ReadPrec (VkSemaphoreImportBitmask a)
-> ReadPrec (VkSemaphoreImportBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkSemaphoreImportBitmask a))]
-> ReadPrec (VkSemaphoreImportBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_SEMAPHORE_IMPORT_TEMPORARY_BIT",
               VkSemaphoreImportBitmask a -> ReadPrec (VkSemaphoreImportBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSemaphoreImportBitmask a
forall (a :: FlagType). VkSemaphoreImportBitmask a
VK_SEMAPHORE_IMPORT_TEMPORARY_BIT)]
             ReadPrec (VkSemaphoreImportBitmask a)
-> ReadPrec (VkSemaphoreImportBitmask a)
-> ReadPrec (VkSemaphoreImportBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkSemaphoreImportBitmask a)
-> ReadPrec (VkSemaphoreImportBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkSemaphoreImportBitmask") ReadPrec ()
-> ReadPrec (VkSemaphoreImportBitmask a)
-> ReadPrec (VkSemaphoreImportBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkSemaphoreImportBitmask a
forall (a :: FlagType). VkFlags -> VkSemaphoreImportBitmask a
VkSemaphoreImportBitmask (VkFlags -> VkSemaphoreImportBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkSemaphoreImportBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | bitpos = @0@
pattern VK_SEMAPHORE_IMPORT_TEMPORARY_BIT ::
        VkSemaphoreImportBitmask a

pattern $bVK_SEMAPHORE_IMPORT_TEMPORARY_BIT :: forall (a :: FlagType). VkSemaphoreImportBitmask a
$mVK_SEMAPHORE_IMPORT_TEMPORARY_BIT :: forall {r} {a :: FlagType}.
VkSemaphoreImportBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SEMAPHORE_IMPORT_TEMPORARY_BIT =
        VkSemaphoreImportBitmask 1

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkSemaphoreType VkSemaphoreType registry at www.khronos.org>
newtype VkSemaphoreType = VkSemaphoreType Int32
                          deriving (VkSemaphoreType -> VkSemaphoreType -> Bool
(VkSemaphoreType -> VkSemaphoreType -> Bool)
-> (VkSemaphoreType -> VkSemaphoreType -> Bool)
-> Eq VkSemaphoreType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c/= :: VkSemaphoreType -> VkSemaphoreType -> Bool
== :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c== :: VkSemaphoreType -> VkSemaphoreType -> Bool
Eq, Eq VkSemaphoreType
Eq VkSemaphoreType
-> (VkSemaphoreType -> VkSemaphoreType -> Ordering)
-> (VkSemaphoreType -> VkSemaphoreType -> Bool)
-> (VkSemaphoreType -> VkSemaphoreType -> Bool)
-> (VkSemaphoreType -> VkSemaphoreType -> Bool)
-> (VkSemaphoreType -> VkSemaphoreType -> Bool)
-> (VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType)
-> (VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType)
-> Ord VkSemaphoreType
VkSemaphoreType -> VkSemaphoreType -> Bool
VkSemaphoreType -> VkSemaphoreType -> Ordering
VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType
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 :: VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType
$cmin :: VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType
max :: VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType
$cmax :: VkSemaphoreType -> VkSemaphoreType -> VkSemaphoreType
>= :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c>= :: VkSemaphoreType -> VkSemaphoreType -> Bool
> :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c> :: VkSemaphoreType -> VkSemaphoreType -> Bool
<= :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c<= :: VkSemaphoreType -> VkSemaphoreType -> Bool
< :: VkSemaphoreType -> VkSemaphoreType -> Bool
$c< :: VkSemaphoreType -> VkSemaphoreType -> Bool
compare :: VkSemaphoreType -> VkSemaphoreType -> Ordering
$ccompare :: VkSemaphoreType -> VkSemaphoreType -> Ordering
Ord, Int -> VkSemaphoreType
VkSemaphoreType -> Int
VkSemaphoreType -> [VkSemaphoreType]
VkSemaphoreType -> VkSemaphoreType
VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
VkSemaphoreType
-> VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
(VkSemaphoreType -> VkSemaphoreType)
-> (VkSemaphoreType -> VkSemaphoreType)
-> (Int -> VkSemaphoreType)
-> (VkSemaphoreType -> Int)
-> (VkSemaphoreType -> [VkSemaphoreType])
-> (VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType])
-> (VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType])
-> (VkSemaphoreType
    -> VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType])
-> Enum VkSemaphoreType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkSemaphoreType
-> VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
$cenumFromThenTo :: VkSemaphoreType
-> VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
enumFromTo :: VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
$cenumFromTo :: VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
enumFromThen :: VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
$cenumFromThen :: VkSemaphoreType -> VkSemaphoreType -> [VkSemaphoreType]
enumFrom :: VkSemaphoreType -> [VkSemaphoreType]
$cenumFrom :: VkSemaphoreType -> [VkSemaphoreType]
fromEnum :: VkSemaphoreType -> Int
$cfromEnum :: VkSemaphoreType -> Int
toEnum :: Int -> VkSemaphoreType
$ctoEnum :: Int -> VkSemaphoreType
pred :: VkSemaphoreType -> VkSemaphoreType
$cpred :: VkSemaphoreType -> VkSemaphoreType
succ :: VkSemaphoreType -> VkSemaphoreType
$csucc :: VkSemaphoreType -> VkSemaphoreType
Enum, Ptr VkSemaphoreType -> IO VkSemaphoreType
Ptr VkSemaphoreType -> Int -> IO VkSemaphoreType
Ptr VkSemaphoreType -> Int -> VkSemaphoreType -> IO ()
Ptr VkSemaphoreType -> VkSemaphoreType -> IO ()
VkSemaphoreType -> Int
(VkSemaphoreType -> Int)
-> (VkSemaphoreType -> Int)
-> (Ptr VkSemaphoreType -> Int -> IO VkSemaphoreType)
-> (Ptr VkSemaphoreType -> Int -> VkSemaphoreType -> IO ())
-> (forall b. Ptr b -> Int -> IO VkSemaphoreType)
-> (forall b. Ptr b -> Int -> VkSemaphoreType -> IO ())
-> (Ptr VkSemaphoreType -> IO VkSemaphoreType)
-> (Ptr VkSemaphoreType -> VkSemaphoreType -> IO ())
-> Storable VkSemaphoreType
forall b. Ptr b -> Int -> IO VkSemaphoreType
forall b. Ptr b -> Int -> VkSemaphoreType -> 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 VkSemaphoreType -> VkSemaphoreType -> IO ()
$cpoke :: Ptr VkSemaphoreType -> VkSemaphoreType -> IO ()
peek :: Ptr VkSemaphoreType -> IO VkSemaphoreType
$cpeek :: Ptr VkSemaphoreType -> IO VkSemaphoreType
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreType -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreType
pokeElemOff :: Ptr VkSemaphoreType -> Int -> VkSemaphoreType -> IO ()
$cpokeElemOff :: Ptr VkSemaphoreType -> Int -> VkSemaphoreType -> IO ()
peekElemOff :: Ptr VkSemaphoreType -> Int -> IO VkSemaphoreType
$cpeekElemOff :: Ptr VkSemaphoreType -> Int -> IO VkSemaphoreType
alignment :: VkSemaphoreType -> Int
$calignment :: VkSemaphoreType -> Int
sizeOf :: VkSemaphoreType -> Int
$csizeOf :: VkSemaphoreType -> Int
Storable)

instance Show VkSemaphoreType where
    showsPrec :: Int -> VkSemaphoreType -> ShowS
showsPrec Int
_ VkSemaphoreType
VK_SEMAPHORE_TYPE_BINARY
      = String -> ShowS
showString String
"VK_SEMAPHORE_TYPE_BINARY"
    showsPrec Int
_ VkSemaphoreType
VK_SEMAPHORE_TYPE_TIMELINE
      = String -> ShowS
showString String
"VK_SEMAPHORE_TYPE_TIMELINE"
    showsPrec Int
p (VkSemaphoreType Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkSemaphoreType " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkSemaphoreType where
    readPrec :: ReadPrec VkSemaphoreType
readPrec
      = ReadPrec VkSemaphoreType -> ReadPrec VkSemaphoreType
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkSemaphoreType)] -> ReadPrec VkSemaphoreType
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_SEMAPHORE_TYPE_BINARY", VkSemaphoreType -> ReadPrec VkSemaphoreType
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSemaphoreType
VK_SEMAPHORE_TYPE_BINARY),
              (String
"VK_SEMAPHORE_TYPE_TIMELINE", VkSemaphoreType -> ReadPrec VkSemaphoreType
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSemaphoreType
VK_SEMAPHORE_TYPE_TIMELINE)]
             ReadPrec VkSemaphoreType
-> ReadPrec VkSemaphoreType -> ReadPrec VkSemaphoreType
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int -> ReadPrec VkSemaphoreType -> ReadPrec VkSemaphoreType
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkSemaphoreType") ReadPrec () -> ReadPrec VkSemaphoreType -> ReadPrec VkSemaphoreType
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkSemaphoreType
VkSemaphoreType (Int32 -> VkSemaphoreType)
-> ReadPrec Int32 -> ReadPrec VkSemaphoreType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_SEMAPHORE_TYPE_BINARY :: VkSemaphoreType

pattern $bVK_SEMAPHORE_TYPE_BINARY :: VkSemaphoreType
$mVK_SEMAPHORE_TYPE_BINARY :: forall {r}. VkSemaphoreType -> (Void# -> r) -> (Void# -> r) -> r
VK_SEMAPHORE_TYPE_BINARY = VkSemaphoreType 0

pattern VK_SEMAPHORE_TYPE_TIMELINE :: VkSemaphoreType

pattern $bVK_SEMAPHORE_TYPE_TIMELINE :: VkSemaphoreType
$mVK_SEMAPHORE_TYPE_TIMELINE :: forall {r}. VkSemaphoreType -> (Void# -> r) -> (Void# -> r) -> r
VK_SEMAPHORE_TYPE_TIMELINE = VkSemaphoreType 1

newtype VkSemaphoreTypeKHR = VkSemaphoreTypeKHR VkFlags
                             deriving (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
(VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> Eq VkSemaphoreTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c/= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
== :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c== :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
Eq, Eq VkSemaphoreTypeKHR
Eq VkSemaphoreTypeKHR
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Ordering)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> Ord VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Ordering
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
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 :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$cmin :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
max :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$cmax :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
>= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c>= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
> :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c> :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
<= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c<= :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
< :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
$c< :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Bool
compare :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Ordering
$ccompare :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> Ordering
Ord, Int -> VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> Int
VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
VkSemaphoreTypeKHR
-> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
(VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int)
-> (VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR])
-> (VkSemaphoreTypeKHR
    -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR])
-> (VkSemaphoreTypeKHR
    -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR])
-> (VkSemaphoreTypeKHR
    -> VkSemaphoreTypeKHR
    -> VkSemaphoreTypeKHR
    -> [VkSemaphoreTypeKHR])
-> Enum VkSemaphoreTypeKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkSemaphoreTypeKHR
-> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
$cenumFromThenTo :: VkSemaphoreTypeKHR
-> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
enumFromTo :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
$cenumFromTo :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
enumFromThen :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
$cenumFromThen :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
enumFrom :: VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
$cenumFrom :: VkSemaphoreTypeKHR -> [VkSemaphoreTypeKHR]
fromEnum :: VkSemaphoreTypeKHR -> Int
$cfromEnum :: VkSemaphoreTypeKHR -> Int
toEnum :: Int -> VkSemaphoreTypeKHR
$ctoEnum :: Int -> VkSemaphoreTypeKHR
pred :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$cpred :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
succ :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$csucc :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
Enum, Eq VkSemaphoreTypeKHR
VkSemaphoreTypeKHR
Eq VkSemaphoreTypeKHR
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> VkSemaphoreTypeKHR
-> (Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> Bool)
-> (VkSemaphoreTypeKHR -> Maybe Int)
-> (VkSemaphoreTypeKHR -> Int)
-> (VkSemaphoreTypeKHR -> Bool)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR)
-> (VkSemaphoreTypeKHR -> Int)
-> Bits VkSemaphoreTypeKHR
Int -> VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> Bool
VkSemaphoreTypeKHR -> Int
VkSemaphoreTypeKHR -> Maybe Int
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> Int -> Bool
VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
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 :: VkSemaphoreTypeKHR -> Int
$cpopCount :: VkSemaphoreTypeKHR -> Int
rotateR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$crotateR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
rotateL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$crotateL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
unsafeShiftR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cunsafeShiftR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
shiftR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cshiftR :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
unsafeShiftL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cunsafeShiftL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
shiftL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cshiftL :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
isSigned :: VkSemaphoreTypeKHR -> Bool
$cisSigned :: VkSemaphoreTypeKHR -> Bool
bitSize :: VkSemaphoreTypeKHR -> Int
$cbitSize :: VkSemaphoreTypeKHR -> Int
bitSizeMaybe :: VkSemaphoreTypeKHR -> Maybe Int
$cbitSizeMaybe :: VkSemaphoreTypeKHR -> Maybe Int
testBit :: VkSemaphoreTypeKHR -> Int -> Bool
$ctestBit :: VkSemaphoreTypeKHR -> Int -> Bool
complementBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$ccomplementBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
clearBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cclearBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
setBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$csetBit :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
bit :: Int -> VkSemaphoreTypeKHR
$cbit :: Int -> VkSemaphoreTypeKHR
zeroBits :: VkSemaphoreTypeKHR
$czeroBits :: VkSemaphoreTypeKHR
rotate :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$crotate :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
shift :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
$cshift :: VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR
complement :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$ccomplement :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
xor :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$cxor :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
.|. :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$c.|. :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
.&. :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
$c.&. :: VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR
Bits, Bits VkSemaphoreTypeKHR
Bits VkSemaphoreTypeKHR
-> (VkSemaphoreTypeKHR -> Int)
-> (VkSemaphoreTypeKHR -> Int)
-> (VkSemaphoreTypeKHR -> Int)
-> FiniteBits VkSemaphoreTypeKHR
VkSemaphoreTypeKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkSemaphoreTypeKHR -> Int
$ccountTrailingZeros :: VkSemaphoreTypeKHR -> Int
countLeadingZeros :: VkSemaphoreTypeKHR -> Int
$ccountLeadingZeros :: VkSemaphoreTypeKHR -> Int
finiteBitSize :: VkSemaphoreTypeKHR -> Int
$cfiniteBitSize :: VkSemaphoreTypeKHR -> Int
FiniteBits, Ptr VkSemaphoreTypeKHR -> IO VkSemaphoreTypeKHR
Ptr VkSemaphoreTypeKHR -> Int -> IO VkSemaphoreTypeKHR
Ptr VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR -> IO ()
Ptr VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> IO ()
VkSemaphoreTypeKHR -> Int
(VkSemaphoreTypeKHR -> Int)
-> (VkSemaphoreTypeKHR -> Int)
-> (Ptr VkSemaphoreTypeKHR -> Int -> IO VkSemaphoreTypeKHR)
-> (Ptr VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkSemaphoreTypeKHR)
-> (forall b. Ptr b -> Int -> VkSemaphoreTypeKHR -> IO ())
-> (Ptr VkSemaphoreTypeKHR -> IO VkSemaphoreTypeKHR)
-> (Ptr VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> IO ())
-> Storable VkSemaphoreTypeKHR
forall b. Ptr b -> Int -> IO VkSemaphoreTypeKHR
forall b. Ptr b -> Int -> VkSemaphoreTypeKHR -> 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 VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> IO ()
$cpoke :: Ptr VkSemaphoreTypeKHR -> VkSemaphoreTypeKHR -> IO ()
peek :: Ptr VkSemaphoreTypeKHR -> IO VkSemaphoreTypeKHR
$cpeek :: Ptr VkSemaphoreTypeKHR -> IO VkSemaphoreTypeKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreTypeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreTypeKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreTypeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreTypeKHR
pokeElemOff :: Ptr VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR -> IO ()
$cpokeElemOff :: Ptr VkSemaphoreTypeKHR -> Int -> VkSemaphoreTypeKHR -> IO ()
peekElemOff :: Ptr VkSemaphoreTypeKHR -> Int -> IO VkSemaphoreTypeKHR
$cpeekElemOff :: Ptr VkSemaphoreTypeKHR -> Int -> IO VkSemaphoreTypeKHR
alignment :: VkSemaphoreTypeKHR -> Int
$calignment :: VkSemaphoreTypeKHR -> Int
sizeOf :: VkSemaphoreTypeKHR -> Int
$csizeOf :: VkSemaphoreTypeKHR -> Int
Storable)

instance Show VkSemaphoreTypeKHR where
    {-# INLINE showsPrec #-}
    showsPrec :: Int -> VkSemaphoreTypeKHR -> ShowS
showsPrec = (Int -> VkFlags -> ShowS) -> Int -> VkSemaphoreTypeKHR -> ShowS
coerce (Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec :: Int -> VkFlags -> ShowS)

instance Read VkSemaphoreTypeKHR where
    {-# INLINE readsPrec #-}
    readsPrec :: Int -> ReadS VkSemaphoreTypeKHR
readsPrec = (Int -> ReadS VkFlags) -> Int -> ReadS VkSemaphoreTypeKHR
coerce (Int -> ReadS VkFlags
forall a. Read a => Int -> ReadS a
readsPrec :: Int -> ReadS VkFlags)

newtype VkSemaphoreWaitFlagBitsKHR = VkSemaphoreWaitFlagBitsKHR VkFlags
                                     deriving (VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
(VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> Eq VkSemaphoreWaitFlagBitsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c/= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
== :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c== :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
Eq, Eq VkSemaphoreWaitFlagBitsKHR
Eq VkSemaphoreWaitFlagBitsKHR
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Ordering)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> Ord VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> Ordering
VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
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 :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$cmin :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
max :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$cmax :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
>= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c>= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
> :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c> :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
<= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c<= :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
< :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
$c< :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR -> Bool
compare :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> Ordering
$ccompare :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> Ordering
Ord, Int -> VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR -> Int
VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> [VkSemaphoreWaitFlagBitsKHR]
(VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> (VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR])
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR])
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR])
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR
    -> [VkSemaphoreWaitFlagBitsKHR])
-> Enum VkSemaphoreWaitFlagBitsKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> [VkSemaphoreWaitFlagBitsKHR]
$cenumFromThenTo :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR
-> [VkSemaphoreWaitFlagBitsKHR]
enumFromTo :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
$cenumFromTo :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
enumFromThen :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
$cenumFromThen :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
enumFrom :: VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
$cenumFrom :: VkSemaphoreWaitFlagBitsKHR -> [VkSemaphoreWaitFlagBitsKHR]
fromEnum :: VkSemaphoreWaitFlagBitsKHR -> Int
$cfromEnum :: VkSemaphoreWaitFlagBitsKHR -> Int
toEnum :: Int -> VkSemaphoreWaitFlagBitsKHR
$ctoEnum :: Int -> VkSemaphoreWaitFlagBitsKHR
pred :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$cpred :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
succ :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$csucc :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
Enum, Eq VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR
Eq VkSemaphoreWaitFlagBitsKHR
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> VkSemaphoreWaitFlagBitsKHR
-> (Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR -> Int -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR -> Maybe Int)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> (VkSemaphoreWaitFlagBitsKHR -> Bool)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> Bits VkSemaphoreWaitFlagBitsKHR
Int -> VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR -> Bool
VkSemaphoreWaitFlagBitsKHR -> Int
VkSemaphoreWaitFlagBitsKHR -> Maybe Int
VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR -> Int -> Bool
VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
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 :: VkSemaphoreWaitFlagBitsKHR -> Int
$cpopCount :: VkSemaphoreWaitFlagBitsKHR -> Int
rotateR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$crotateR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
rotateL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$crotateL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
unsafeShiftR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cunsafeShiftR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
shiftR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cshiftR :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
unsafeShiftL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cunsafeShiftL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
shiftL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cshiftL :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
isSigned :: VkSemaphoreWaitFlagBitsKHR -> Bool
$cisSigned :: VkSemaphoreWaitFlagBitsKHR -> Bool
bitSize :: VkSemaphoreWaitFlagBitsKHR -> Int
$cbitSize :: VkSemaphoreWaitFlagBitsKHR -> Int
bitSizeMaybe :: VkSemaphoreWaitFlagBitsKHR -> Maybe Int
$cbitSizeMaybe :: VkSemaphoreWaitFlagBitsKHR -> Maybe Int
testBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> Bool
$ctestBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> Bool
complementBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$ccomplementBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
clearBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cclearBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
setBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$csetBit :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
bit :: Int -> VkSemaphoreWaitFlagBitsKHR
$cbit :: Int -> VkSemaphoreWaitFlagBitsKHR
zeroBits :: VkSemaphoreWaitFlagBitsKHR
$czeroBits :: VkSemaphoreWaitFlagBitsKHR
rotate :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$crotate :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
shift :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
$cshift :: VkSemaphoreWaitFlagBitsKHR -> Int -> VkSemaphoreWaitFlagBitsKHR
complement :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$ccomplement :: VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
xor :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$cxor :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
.|. :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$c.|. :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
.&. :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
$c.&. :: VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> VkSemaphoreWaitFlagBitsKHR
Bits, Bits VkSemaphoreWaitFlagBitsKHR
Bits VkSemaphoreWaitFlagBitsKHR
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> FiniteBits VkSemaphoreWaitFlagBitsKHR
VkSemaphoreWaitFlagBitsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkSemaphoreWaitFlagBitsKHR -> Int
$ccountTrailingZeros :: VkSemaphoreWaitFlagBitsKHR -> Int
countLeadingZeros :: VkSemaphoreWaitFlagBitsKHR -> Int
$ccountLeadingZeros :: VkSemaphoreWaitFlagBitsKHR -> Int
finiteBitSize :: VkSemaphoreWaitFlagBitsKHR -> Int
$cfiniteBitSize :: VkSemaphoreWaitFlagBitsKHR -> Int
FiniteBits, Ptr VkSemaphoreWaitFlagBitsKHR -> IO VkSemaphoreWaitFlagBitsKHR
Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> IO VkSemaphoreWaitFlagBitsKHR
Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ()
Ptr VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> IO ()
VkSemaphoreWaitFlagBitsKHR -> Int
(VkSemaphoreWaitFlagBitsKHR -> Int)
-> (VkSemaphoreWaitFlagBitsKHR -> Int)
-> (Ptr VkSemaphoreWaitFlagBitsKHR
    -> Int -> IO VkSemaphoreWaitFlagBitsKHR)
-> (Ptr VkSemaphoreWaitFlagBitsKHR
    -> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkSemaphoreWaitFlagBitsKHR)
-> (forall b. Ptr b -> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ())
-> (Ptr VkSemaphoreWaitFlagBitsKHR
    -> IO VkSemaphoreWaitFlagBitsKHR)
-> (Ptr VkSemaphoreWaitFlagBitsKHR
    -> VkSemaphoreWaitFlagBitsKHR -> IO ())
-> Storable VkSemaphoreWaitFlagBitsKHR
forall b. Ptr b -> Int -> IO VkSemaphoreWaitFlagBitsKHR
forall b. Ptr b -> Int -> VkSemaphoreWaitFlagBitsKHR -> 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 VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> IO ()
$cpoke :: Ptr VkSemaphoreWaitFlagBitsKHR
-> VkSemaphoreWaitFlagBitsKHR -> IO ()
peek :: Ptr VkSemaphoreWaitFlagBitsKHR -> IO VkSemaphoreWaitFlagBitsKHR
$cpeek :: Ptr VkSemaphoreWaitFlagBitsKHR -> IO VkSemaphoreWaitFlagBitsKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreWaitFlagBitsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkSemaphoreWaitFlagBitsKHR
pokeElemOff :: Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ()
$cpokeElemOff :: Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> VkSemaphoreWaitFlagBitsKHR -> IO ()
peekElemOff :: Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> IO VkSemaphoreWaitFlagBitsKHR
$cpeekElemOff :: Ptr VkSemaphoreWaitFlagBitsKHR
-> Int -> IO VkSemaphoreWaitFlagBitsKHR
alignment :: VkSemaphoreWaitFlagBitsKHR -> Int
$calignment :: VkSemaphoreWaitFlagBitsKHR -> Int
sizeOf :: VkSemaphoreWaitFlagBitsKHR -> Int
$csizeOf :: VkSemaphoreWaitFlagBitsKHR -> Int
Storable)

instance Show VkSemaphoreWaitFlagBitsKHR where
    {-# INLINE showsPrec #-}
    showsPrec :: Int -> VkSemaphoreWaitFlagBitsKHR -> ShowS
showsPrec = (Int -> VkFlags -> ShowS)
-> Int -> VkSemaphoreWaitFlagBitsKHR -> ShowS
coerce (Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec :: Int -> VkFlags -> ShowS)

instance Read VkSemaphoreWaitFlagBitsKHR where
    {-# INLINE readsPrec #-}
    readsPrec :: Int -> ReadS VkSemaphoreWaitFlagBitsKHR
readsPrec = (Int -> ReadS VkFlags) -> Int -> ReadS VkSemaphoreWaitFlagBitsKHR
coerce (Int -> ReadS VkFlags
forall a. Read a => Int -> ReadS a
readsPrec :: Int -> ReadS VkFlags)

newtype VkSemaphoreWaitBitmask (a ::
                                  FlagType) = VkSemaphoreWaitBitmask VkFlags
                                              deriving (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
(VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> Eq (VkSemaphoreWaitBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
/= :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
== :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
Eq, Eq (VkSemaphoreWaitBitmask a)
Eq (VkSemaphoreWaitBitmask a)
-> (VkSemaphoreWaitBitmask a
    -> VkSemaphoreWaitBitmask a -> Ordering)
-> (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> (VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool)
-> (VkSemaphoreWaitBitmask a
    -> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a)
-> (VkSemaphoreWaitBitmask a
    -> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a)
-> Ord (VkSemaphoreWaitBitmask a)
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Ordering
VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
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
forall (a :: FlagType). Eq (VkSemaphoreWaitBitmask a)
forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Ordering
forall (a :: FlagType).
VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
min :: VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
$cmin :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
max :: VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
$cmax :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a
-> VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a
>= :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
> :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
<= :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
< :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Bool
compare :: VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkSemaphoreWaitBitmask a -> VkSemaphoreWaitBitmask a -> Ordering
Ord, Ptr (VkSemaphoreWaitBitmask a) -> IO (VkSemaphoreWaitBitmask a)
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> IO (VkSemaphoreWaitBitmask a)
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> VkSemaphoreWaitBitmask a -> IO ()
Ptr (VkSemaphoreWaitBitmask a) -> VkSemaphoreWaitBitmask a -> IO ()
VkSemaphoreWaitBitmask a -> Int
(VkSemaphoreWaitBitmask a -> Int)
-> (VkSemaphoreWaitBitmask a -> Int)
-> (Ptr (VkSemaphoreWaitBitmask a)
    -> Int -> IO (VkSemaphoreWaitBitmask a))
-> (Ptr (VkSemaphoreWaitBitmask a)
    -> Int -> VkSemaphoreWaitBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkSemaphoreWaitBitmask a))
-> (forall b. Ptr b -> Int -> VkSemaphoreWaitBitmask a -> IO ())
-> (Ptr (VkSemaphoreWaitBitmask a)
    -> IO (VkSemaphoreWaitBitmask a))
-> (Ptr (VkSemaphoreWaitBitmask a)
    -> VkSemaphoreWaitBitmask a -> IO ())
-> Storable (VkSemaphoreWaitBitmask a)
forall b. Ptr b -> Int -> IO (VkSemaphoreWaitBitmask a)
forall b. Ptr b -> Int -> VkSemaphoreWaitBitmask a -> 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
forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a) -> IO (VkSemaphoreWaitBitmask a)
forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> IO (VkSemaphoreWaitBitmask a)
forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> VkSemaphoreWaitBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a) -> VkSemaphoreWaitBitmask a -> IO ()
forall (a :: FlagType). VkSemaphoreWaitBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSemaphoreWaitBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkSemaphoreWaitBitmask a -> IO ()
poke :: Ptr (VkSemaphoreWaitBitmask a) -> VkSemaphoreWaitBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a) -> VkSemaphoreWaitBitmask a -> IO ()
peek :: Ptr (VkSemaphoreWaitBitmask a) -> IO (VkSemaphoreWaitBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a) -> IO (VkSemaphoreWaitBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkSemaphoreWaitBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkSemaphoreWaitBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkSemaphoreWaitBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSemaphoreWaitBitmask a)
pokeElemOff :: Ptr (VkSemaphoreWaitBitmask a)
-> Int -> VkSemaphoreWaitBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> VkSemaphoreWaitBitmask a -> IO ()
peekElemOff :: Ptr (VkSemaphoreWaitBitmask a)
-> Int -> IO (VkSemaphoreWaitBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkSemaphoreWaitBitmask a)
-> Int -> IO (VkSemaphoreWaitBitmask a)
alignment :: VkSemaphoreWaitBitmask a -> Int
$calignment :: forall (a :: FlagType). VkSemaphoreWaitBitmask a -> Int
sizeOf :: VkSemaphoreWaitBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkSemaphoreWaitBitmask a -> Int
Storable)

type VkSemaphoreWaitFlags = VkSemaphoreWaitBitmask FlagMask

type VkSemaphoreWaitFlagBits = VkSemaphoreWaitBitmask FlagBit

pattern VkSemaphoreWaitFlagBits ::
        VkFlags -> VkSemaphoreWaitBitmask FlagBit

pattern $bVkSemaphoreWaitFlagBits :: VkFlags -> VkSemaphoreWaitBitmask FlagBit
$mVkSemaphoreWaitFlagBits :: forall {r}.
VkSemaphoreWaitBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSemaphoreWaitFlagBits n = VkSemaphoreWaitBitmask n

pattern VkSemaphoreWaitFlags ::
        VkFlags -> VkSemaphoreWaitBitmask FlagMask

pattern $bVkSemaphoreWaitFlags :: VkFlags -> VkSemaphoreWaitBitmask FlagMask
$mVkSemaphoreWaitFlags :: forall {r}.
VkSemaphoreWaitBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSemaphoreWaitFlags n = VkSemaphoreWaitBitmask n

deriving instance Bits (VkSemaphoreWaitBitmask FlagMask)

deriving instance FiniteBits (VkSemaphoreWaitBitmask FlagMask)

instance Show (VkSemaphoreWaitBitmask a) where
    showsPrec :: Int -> VkSemaphoreWaitBitmask a -> ShowS
showsPrec Int
_ VkSemaphoreWaitBitmask a
VK_SEMAPHORE_WAIT_ANY_BIT
      = String -> ShowS
showString String
"VK_SEMAPHORE_WAIT_ANY_BIT"
    showsPrec Int
p (VkSemaphoreWaitBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkSemaphoreWaitBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkSemaphoreWaitBitmask a) where
    readPrec :: ReadPrec (VkSemaphoreWaitBitmask a)
readPrec
      = ReadPrec (VkSemaphoreWaitBitmask a)
-> ReadPrec (VkSemaphoreWaitBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkSemaphoreWaitBitmask a))]
-> ReadPrec (VkSemaphoreWaitBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_SEMAPHORE_WAIT_ANY_BIT", VkSemaphoreWaitBitmask a -> ReadPrec (VkSemaphoreWaitBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSemaphoreWaitBitmask a
forall (a :: FlagType). VkSemaphoreWaitBitmask a
VK_SEMAPHORE_WAIT_ANY_BIT)]
             ReadPrec (VkSemaphoreWaitBitmask a)
-> ReadPrec (VkSemaphoreWaitBitmask a)
-> ReadPrec (VkSemaphoreWaitBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkSemaphoreWaitBitmask a)
-> ReadPrec (VkSemaphoreWaitBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkSemaphoreWaitBitmask") ReadPrec ()
-> ReadPrec (VkSemaphoreWaitBitmask a)
-> ReadPrec (VkSemaphoreWaitBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkSemaphoreWaitBitmask a
forall (a :: FlagType). VkFlags -> VkSemaphoreWaitBitmask a
VkSemaphoreWaitBitmask (VkFlags -> VkSemaphoreWaitBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkSemaphoreWaitBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | bitpos = @0@
pattern VK_SEMAPHORE_WAIT_ANY_BIT :: VkSemaphoreWaitBitmask a

pattern $bVK_SEMAPHORE_WAIT_ANY_BIT :: forall (a :: FlagType). VkSemaphoreWaitBitmask a
$mVK_SEMAPHORE_WAIT_ANY_BIT :: forall {r} {a :: FlagType}.
VkSemaphoreWaitBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SEMAPHORE_WAIT_ANY_BIT = VkSemaphoreWaitBitmask 1