{-# language CPP #-}
-- No documentation found for Chapter "SemaphoreCreateFlags"
module Vulkan.Core10.Enums.SemaphoreCreateFlags  (SemaphoreCreateFlags(..)) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
-- | VkSemaphoreCreateFlags - Reserved for future use
--
-- = Description
--
-- 'SemaphoreCreateFlags' is a bitmask type for setting a mask, but is
-- currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.QueueSemaphore.SemaphoreCreateInfo'
newtype SemaphoreCreateFlags = SemaphoreCreateFlags Flags
  deriving newtype (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
(SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> Eq SemaphoreCreateFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c/= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
Eq, Eq SemaphoreCreateFlags
Eq SemaphoreCreateFlags
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> Ord SemaphoreCreateFlags
SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
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 :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cmin :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
max :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cmax :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
>= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c>= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
> :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c> :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
<= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c<= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
< :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c< :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
compare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
$ccompare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
Ord, Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
SemaphoreCreateFlags -> Int
(SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> (Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags)
-> (Ptr SemaphoreCreateFlags
    -> Int -> SemaphoreCreateFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO SemaphoreCreateFlags)
-> (forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ())
-> (Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags)
-> (Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ())
-> Storable SemaphoreCreateFlags
forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
forall b. Ptr b -> Int -> SemaphoreCreateFlags -> 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 SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
$cpoke :: Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
peek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
$cpeek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
pokeByteOff :: forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
pokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
$cpokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
peekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
$cpeekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
alignment :: SemaphoreCreateFlags -> Int
$calignment :: SemaphoreCreateFlags -> Int
sizeOf :: SemaphoreCreateFlags -> Int
$csizeOf :: SemaphoreCreateFlags -> Int
Storable, SemaphoreCreateFlags
SemaphoreCreateFlags -> Zero SemaphoreCreateFlags
forall a. a -> Zero a
zero :: SemaphoreCreateFlags
$czero :: SemaphoreCreateFlags
Zero, Eq SemaphoreCreateFlags
SemaphoreCreateFlags
Eq SemaphoreCreateFlags
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> SemaphoreCreateFlags
-> (Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> Bool)
-> (SemaphoreCreateFlags -> Maybe Int)
-> (SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int)
-> Bits SemaphoreCreateFlags
Int -> SemaphoreCreateFlags
SemaphoreCreateFlags -> Bool
SemaphoreCreateFlags -> Int
SemaphoreCreateFlags -> Maybe Int
SemaphoreCreateFlags -> SemaphoreCreateFlags
SemaphoreCreateFlags -> Int -> Bool
SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
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 :: SemaphoreCreateFlags -> Int
$cpopCount :: SemaphoreCreateFlags -> Int
rotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
rotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
isSigned :: SemaphoreCreateFlags -> Bool
$cisSigned :: SemaphoreCreateFlags -> Bool
bitSize :: SemaphoreCreateFlags -> Int
$cbitSize :: SemaphoreCreateFlags -> Int
bitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
$cbitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
testBit :: SemaphoreCreateFlags -> Int -> Bool
$ctestBit :: SemaphoreCreateFlags -> Int -> Bool
complementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$ccomplementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
clearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cclearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
setBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$csetBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
bit :: Int -> SemaphoreCreateFlags
$cbit :: Int -> SemaphoreCreateFlags
zeroBits :: SemaphoreCreateFlags
$czeroBits :: SemaphoreCreateFlags
rotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
complement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
$ccomplement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
xor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cxor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$c.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$c.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
Bits, Bits SemaphoreCreateFlags
Bits SemaphoreCreateFlags
-> (SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> FiniteBits SemaphoreCreateFlags
SemaphoreCreateFlags -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: SemaphoreCreateFlags -> Int
$ccountTrailingZeros :: SemaphoreCreateFlags -> Int
countLeadingZeros :: SemaphoreCreateFlags -> Int
$ccountLeadingZeros :: SemaphoreCreateFlags -> Int
finiteBitSize :: SemaphoreCreateFlags -> Int
$cfiniteBitSize :: SemaphoreCreateFlags -> Int
FiniteBits)

conNameSemaphoreCreateFlags :: String
conNameSemaphoreCreateFlags :: String
conNameSemaphoreCreateFlags = String
"SemaphoreCreateFlags"

enumPrefixSemaphoreCreateFlags :: String
enumPrefixSemaphoreCreateFlags :: String
enumPrefixSemaphoreCreateFlags = String
""

showTableSemaphoreCreateFlags :: [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags :: [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags = []

instance Show SemaphoreCreateFlags where
  showsPrec :: Int -> SemaphoreCreateFlags -> ShowS
showsPrec =
    String
-> [(SemaphoreCreateFlags, String)]
-> String
-> (SemaphoreCreateFlags -> Flags)
-> (Flags -> ShowS)
-> Int
-> SemaphoreCreateFlags
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixSemaphoreCreateFlags
      [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags
      String
conNameSemaphoreCreateFlags
      (\(SemaphoreCreateFlags 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, Show a) => a -> ShowS
showHex Flags
x)

instance Read SemaphoreCreateFlags where
  readPrec :: ReadPrec SemaphoreCreateFlags
readPrec =
    String
-> [(SemaphoreCreateFlags, String)]
-> String
-> (Flags -> SemaphoreCreateFlags)
-> ReadPrec SemaphoreCreateFlags
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixSemaphoreCreateFlags
      [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags
      String
conNameSemaphoreCreateFlags
      Flags -> SemaphoreCreateFlags
SemaphoreCreateFlags