{-# language CPP #-}
-- No documentation found for Chapter "QueryPoolCreateFlags"
module Vulkan.Core10.Enums.QueryPoolCreateFlags  (QueryPoolCreateFlags(..)) 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)
-- | VkQueryPoolCreateFlags - Reserved for future use
--
-- = Description
--
-- 'QueryPoolCreateFlags' 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.Query.QueryPoolCreateInfo'
newtype QueryPoolCreateFlags = QueryPoolCreateFlags Flags
  deriving newtype (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
(QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> Eq QueryPoolCreateFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c/= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
== :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c== :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
Eq, Eq QueryPoolCreateFlags
Eq QueryPoolCreateFlags
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Ordering)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags
    -> QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags
    -> QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> Ord QueryPoolCreateFlags
QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
QueryPoolCreateFlags -> QueryPoolCreateFlags -> Ordering
QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
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 :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$cmin :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
max :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$cmax :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
>= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c>= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
> :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c> :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
<= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c<= :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
< :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
$c< :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Bool
compare :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Ordering
$ccompare :: QueryPoolCreateFlags -> QueryPoolCreateFlags -> Ordering
$cp1Ord :: Eq QueryPoolCreateFlags
Ord, Ptr b -> Int -> IO QueryPoolCreateFlags
Ptr b -> Int -> QueryPoolCreateFlags -> IO ()
Ptr QueryPoolCreateFlags -> IO QueryPoolCreateFlags
Ptr QueryPoolCreateFlags -> Int -> IO QueryPoolCreateFlags
Ptr QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags -> IO ()
Ptr QueryPoolCreateFlags -> QueryPoolCreateFlags -> IO ()
QueryPoolCreateFlags -> Int
(QueryPoolCreateFlags -> Int)
-> (QueryPoolCreateFlags -> Int)
-> (Ptr QueryPoolCreateFlags -> Int -> IO QueryPoolCreateFlags)
-> (Ptr QueryPoolCreateFlags
    -> Int -> QueryPoolCreateFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO QueryPoolCreateFlags)
-> (forall b. Ptr b -> Int -> QueryPoolCreateFlags -> IO ())
-> (Ptr QueryPoolCreateFlags -> IO QueryPoolCreateFlags)
-> (Ptr QueryPoolCreateFlags -> QueryPoolCreateFlags -> IO ())
-> Storable QueryPoolCreateFlags
forall b. Ptr b -> Int -> IO QueryPoolCreateFlags
forall b. Ptr b -> Int -> QueryPoolCreateFlags -> 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 QueryPoolCreateFlags -> QueryPoolCreateFlags -> IO ()
$cpoke :: Ptr QueryPoolCreateFlags -> QueryPoolCreateFlags -> IO ()
peek :: Ptr QueryPoolCreateFlags -> IO QueryPoolCreateFlags
$cpeek :: Ptr QueryPoolCreateFlags -> IO QueryPoolCreateFlags
pokeByteOff :: Ptr b -> Int -> QueryPoolCreateFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueryPoolCreateFlags -> IO ()
peekByteOff :: Ptr b -> Int -> IO QueryPoolCreateFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueryPoolCreateFlags
pokeElemOff :: Ptr QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags -> IO ()
$cpokeElemOff :: Ptr QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags -> IO ()
peekElemOff :: Ptr QueryPoolCreateFlags -> Int -> IO QueryPoolCreateFlags
$cpeekElemOff :: Ptr QueryPoolCreateFlags -> Int -> IO QueryPoolCreateFlags
alignment :: QueryPoolCreateFlags -> Int
$calignment :: QueryPoolCreateFlags -> Int
sizeOf :: QueryPoolCreateFlags -> Int
$csizeOf :: QueryPoolCreateFlags -> Int
Storable, QueryPoolCreateFlags
QueryPoolCreateFlags -> Zero QueryPoolCreateFlags
forall a. a -> Zero a
zero :: QueryPoolCreateFlags
$czero :: QueryPoolCreateFlags
Zero, Eq QueryPoolCreateFlags
QueryPoolCreateFlags
Eq QueryPoolCreateFlags
-> (QueryPoolCreateFlags
    -> QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags
    -> QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags
    -> QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> QueryPoolCreateFlags
-> (Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> Bool)
-> (QueryPoolCreateFlags -> Maybe Int)
-> (QueryPoolCreateFlags -> Int)
-> (QueryPoolCreateFlags -> Bool)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags)
-> (QueryPoolCreateFlags -> Int)
-> Bits QueryPoolCreateFlags
Int -> QueryPoolCreateFlags
QueryPoolCreateFlags -> Bool
QueryPoolCreateFlags -> Int
QueryPoolCreateFlags -> Maybe Int
QueryPoolCreateFlags -> QueryPoolCreateFlags
QueryPoolCreateFlags -> Int -> Bool
QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
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 :: QueryPoolCreateFlags -> Int
$cpopCount :: QueryPoolCreateFlags -> Int
rotateR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$crotateR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
rotateL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$crotateL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
unsafeShiftR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cunsafeShiftR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
shiftR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cshiftR :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
unsafeShiftL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cunsafeShiftL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
shiftL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cshiftL :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
isSigned :: QueryPoolCreateFlags -> Bool
$cisSigned :: QueryPoolCreateFlags -> Bool
bitSize :: QueryPoolCreateFlags -> Int
$cbitSize :: QueryPoolCreateFlags -> Int
bitSizeMaybe :: QueryPoolCreateFlags -> Maybe Int
$cbitSizeMaybe :: QueryPoolCreateFlags -> Maybe Int
testBit :: QueryPoolCreateFlags -> Int -> Bool
$ctestBit :: QueryPoolCreateFlags -> Int -> Bool
complementBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$ccomplementBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
clearBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cclearBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
setBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$csetBit :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
bit :: Int -> QueryPoolCreateFlags
$cbit :: Int -> QueryPoolCreateFlags
zeroBits :: QueryPoolCreateFlags
$czeroBits :: QueryPoolCreateFlags
rotate :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$crotate :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
shift :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
$cshift :: QueryPoolCreateFlags -> Int -> QueryPoolCreateFlags
complement :: QueryPoolCreateFlags -> QueryPoolCreateFlags
$ccomplement :: QueryPoolCreateFlags -> QueryPoolCreateFlags
xor :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$cxor :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
.|. :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$c.|. :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
.&. :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$c.&. :: QueryPoolCreateFlags
-> QueryPoolCreateFlags -> QueryPoolCreateFlags
$cp1Bits :: Eq QueryPoolCreateFlags
Bits, Bits QueryPoolCreateFlags
Bits QueryPoolCreateFlags
-> (QueryPoolCreateFlags -> Int)
-> (QueryPoolCreateFlags -> Int)
-> (QueryPoolCreateFlags -> Int)
-> FiniteBits QueryPoolCreateFlags
QueryPoolCreateFlags -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: QueryPoolCreateFlags -> Int
$ccountTrailingZeros :: QueryPoolCreateFlags -> Int
countLeadingZeros :: QueryPoolCreateFlags -> Int
$ccountLeadingZeros :: QueryPoolCreateFlags -> Int
finiteBitSize :: QueryPoolCreateFlags -> Int
$cfiniteBitSize :: QueryPoolCreateFlags -> Int
$cp1FiniteBits :: Bits QueryPoolCreateFlags
FiniteBits)



conNameQueryPoolCreateFlags :: String
conNameQueryPoolCreateFlags :: String
conNameQueryPoolCreateFlags = String
"QueryPoolCreateFlags"

enumPrefixQueryPoolCreateFlags :: String
enumPrefixQueryPoolCreateFlags :: String
enumPrefixQueryPoolCreateFlags = String
""

showTableQueryPoolCreateFlags :: [(QueryPoolCreateFlags, String)]
showTableQueryPoolCreateFlags :: [(QueryPoolCreateFlags, String)]
showTableQueryPoolCreateFlags = []

instance Show QueryPoolCreateFlags where
  showsPrec :: Int -> QueryPoolCreateFlags -> ShowS
showsPrec = String
-> [(QueryPoolCreateFlags, String)]
-> String
-> (QueryPoolCreateFlags -> Flags)
-> (Flags -> ShowS)
-> Int
-> QueryPoolCreateFlags
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixQueryPoolCreateFlags
                            [(QueryPoolCreateFlags, String)]
showTableQueryPoolCreateFlags
                            String
conNameQueryPoolCreateFlags
                            (\(QueryPoolCreateFlags 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 QueryPoolCreateFlags where
  readPrec :: ReadPrec QueryPoolCreateFlags
readPrec = String
-> [(QueryPoolCreateFlags, String)]
-> String
-> (Flags -> QueryPoolCreateFlags)
-> ReadPrec QueryPoolCreateFlags
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixQueryPoolCreateFlags
                          [(QueryPoolCreateFlags, String)]
showTableQueryPoolCreateFlags
                          String
conNameQueryPoolCreateFlags
                          Flags -> QueryPoolCreateFlags
QueryPoolCreateFlags