{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Query
       (VkQueryControlBitmask(VkQueryControlBitmask, VkQueryControlFlags,
                              VkQueryControlFlagBits, VK_QUERY_CONTROL_PRECISE_BIT),
        VkQueryControlFlags, VkQueryControlFlagBits,
        VkQueryPipelineStatisticBitmask(VkQueryPipelineStatisticBitmask,
                                        VkQueryPipelineStatisticFlags,
                                        VkQueryPipelineStatisticFlagBits,
                                        VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT,
                                        VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT),
        VkQueryPipelineStatisticFlags, VkQueryPipelineStatisticFlagBits,
        VkQueryPoolCreateFlagBits(..),
        VkQueryResultBitmask(VkQueryResultBitmask, VkQueryResultFlags,
                             VkQueryResultFlagBits, VK_QUERY_RESULT_64_BIT,
                             VK_QUERY_RESULT_WAIT_BIT, VK_QUERY_RESULT_WITH_AVAILABILITY_BIT,
                             VK_QUERY_RESULT_PARTIAL_BIT),
        VkQueryResultFlags, VkQueryResultFlagBits,
        VkQueryType(VkQueryType, VK_QUERY_TYPE_OCCLUSION,
                    VK_QUERY_TYPE_PIPELINE_STATISTICS, VK_QUERY_TYPE_TIMESTAMP))
       where
import           Data.Bits                       (Bits, FiniteBits)
import           Data.Coerce                     (coerce)
import           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
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 VkQueryControlBitmask (a ::
                                 FlagType) = VkQueryControlBitmask VkFlags
                                               deriving (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
(VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> Eq (VkQueryControlBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
/= :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
== :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
Eq, Eq (VkQueryControlBitmask a)
Eq (VkQueryControlBitmask a)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Ordering)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> (VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool)
-> (VkQueryControlBitmask a
    -> VkQueryControlBitmask a -> VkQueryControlBitmask a)
-> (VkQueryControlBitmask a
    -> VkQueryControlBitmask a -> VkQueryControlBitmask a)
-> Ord (VkQueryControlBitmask a)
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Ordering
VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask 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 (VkQueryControlBitmask a)
forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Ordering
forall (a :: FlagType).
VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
min :: VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
$cmin :: forall (a :: FlagType).
VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
max :: VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
$cmax :: forall (a :: FlagType).
VkQueryControlBitmask a
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
>= :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
> :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
<= :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
< :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Bool
compare :: VkQueryControlBitmask a -> VkQueryControlBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkQueryControlBitmask a -> VkQueryControlBitmask a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkQueryControlBitmask a)
Ord, Ptr b -> Int -> IO (VkQueryControlBitmask a)
Ptr b -> Int -> VkQueryControlBitmask a -> IO ()
Ptr (VkQueryControlBitmask a) -> IO (VkQueryControlBitmask a)
Ptr (VkQueryControlBitmask a)
-> Int -> IO (VkQueryControlBitmask a)
Ptr (VkQueryControlBitmask a)
-> Int -> VkQueryControlBitmask a -> IO ()
Ptr (VkQueryControlBitmask a) -> VkQueryControlBitmask a -> IO ()
VkQueryControlBitmask a -> Int
(VkQueryControlBitmask a -> Int)
-> (VkQueryControlBitmask a -> Int)
-> (Ptr (VkQueryControlBitmask a)
    -> Int -> IO (VkQueryControlBitmask a))
-> (Ptr (VkQueryControlBitmask a)
    -> Int -> VkQueryControlBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkQueryControlBitmask a))
-> (forall b. Ptr b -> Int -> VkQueryControlBitmask a -> IO ())
-> (Ptr (VkQueryControlBitmask a) -> IO (VkQueryControlBitmask a))
-> (Ptr (VkQueryControlBitmask a)
    -> VkQueryControlBitmask a -> IO ())
-> Storable (VkQueryControlBitmask a)
forall b. Ptr b -> Int -> IO (VkQueryControlBitmask a)
forall b. Ptr b -> Int -> VkQueryControlBitmask 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 (VkQueryControlBitmask a) -> IO (VkQueryControlBitmask a)
forall (a :: FlagType).
Ptr (VkQueryControlBitmask a)
-> Int -> IO (VkQueryControlBitmask a)
forall (a :: FlagType).
Ptr (VkQueryControlBitmask a)
-> Int -> VkQueryControlBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkQueryControlBitmask a) -> VkQueryControlBitmask a -> IO ()
forall (a :: FlagType). VkQueryControlBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryControlBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryControlBitmask a -> IO ()
poke :: Ptr (VkQueryControlBitmask a) -> VkQueryControlBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkQueryControlBitmask a) -> VkQueryControlBitmask a -> IO ()
peek :: Ptr (VkQueryControlBitmask a) -> IO (VkQueryControlBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkQueryControlBitmask a) -> IO (VkQueryControlBitmask a)
pokeByteOff :: Ptr b -> Int -> VkQueryControlBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryControlBitmask a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkQueryControlBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryControlBitmask a)
pokeElemOff :: Ptr (VkQueryControlBitmask a)
-> Int -> VkQueryControlBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkQueryControlBitmask a)
-> Int -> VkQueryControlBitmask a -> IO ()
peekElemOff :: Ptr (VkQueryControlBitmask a)
-> Int -> IO (VkQueryControlBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkQueryControlBitmask a)
-> Int -> IO (VkQueryControlBitmask a)
alignment :: VkQueryControlBitmask a -> Int
$calignment :: forall (a :: FlagType). VkQueryControlBitmask a -> Int
sizeOf :: VkQueryControlBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkQueryControlBitmask a -> Int
Storable, Typeable (VkQueryControlBitmask a)
DataType
Constr
Typeable (VkQueryControlBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkQueryControlBitmask a
    -> c (VkQueryControlBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a))
-> (VkQueryControlBitmask a -> Constr)
-> (VkQueryControlBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkQueryControlBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkQueryControlBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkQueryControlBitmask a -> VkQueryControlBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryControlBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryControlBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryControlBitmask a -> m (VkQueryControlBitmask a))
-> Data (VkQueryControlBitmask a)
VkQueryControlBitmask a -> DataType
VkQueryControlBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryControlBitmask a
-> c (VkQueryControlBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryControlBitmask a)
forall (a :: FlagType).
Typeable a =>
VkQueryControlBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkQueryControlBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryControlBitmask a
-> c (VkQueryControlBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryControlBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryControlBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryControlBitmask a
-> c (VkQueryControlBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryControlBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryControlBitmask a))
$cVkQueryControlBitmask :: Constr
$tVkQueryControlBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryControlBitmask a -> m (VkQueryControlBitmask a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueryControlBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryControlBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryControlBitmask a -> VkQueryControlBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryControlBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryControlBitmask a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkQueryControlBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryControlBitmask a))
dataTypeOf :: VkQueryControlBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkQueryControlBitmask a -> DataType
toConstr :: VkQueryControlBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkQueryControlBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryControlBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryControlBitmask a
-> c (VkQueryControlBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryControlBitmask a
-> c (VkQueryControlBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryControlBitmask a)
Data, (forall x.
 VkQueryControlBitmask a -> Rep (VkQueryControlBitmask a) x)
-> (forall x.
    Rep (VkQueryControlBitmask a) x -> VkQueryControlBitmask a)
-> Generic (VkQueryControlBitmask a)
forall x.
Rep (VkQueryControlBitmask a) x -> VkQueryControlBitmask a
forall x.
VkQueryControlBitmask a -> Rep (VkQueryControlBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkQueryControlBitmask a) x -> VkQueryControlBitmask a
forall (a :: FlagType) x.
VkQueryControlBitmask a -> Rep (VkQueryControlBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkQueryControlBitmask a) x -> VkQueryControlBitmask a
$cfrom :: forall (a :: FlagType) x.
VkQueryControlBitmask a -> Rep (VkQueryControlBitmask a) x
Generic)

type VkQueryControlFlags = VkQueryControlBitmask FlagMask

type VkQueryControlFlagBits = VkQueryControlBitmask FlagBit

pattern VkQueryControlFlagBits ::
        VkFlags -> VkQueryControlBitmask FlagBit

pattern $bVkQueryControlFlagBits :: VkFlags -> VkQueryControlBitmask FlagBit
$mVkQueryControlFlagBits :: forall r.
VkQueryControlBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryControlFlagBits n = VkQueryControlBitmask n

pattern VkQueryControlFlags ::
        VkFlags -> VkQueryControlBitmask FlagMask

pattern $bVkQueryControlFlags :: VkFlags -> VkQueryControlBitmask FlagMask
$mVkQueryControlFlags :: forall r.
VkQueryControlBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryControlFlags n = VkQueryControlBitmask n

deriving instance Bits (VkQueryControlBitmask FlagMask)

deriving instance FiniteBits (VkQueryControlBitmask FlagMask)

deriving instance Integral (VkQueryControlBitmask FlagMask)

deriving instance Num (VkQueryControlBitmask FlagMask)

deriving instance Bounded (VkQueryControlBitmask FlagMask)

deriving instance Enum (VkQueryControlBitmask FlagMask)

deriving instance Real (VkQueryControlBitmask FlagMask)

instance Show (VkQueryControlBitmask a) where
        showsPrec :: Int -> VkQueryControlBitmask a -> ShowS
showsPrec Int
_ VkQueryControlBitmask a
VK_QUERY_CONTROL_PRECISE_BIT
          = String -> ShowS
showString String
"VK_QUERY_CONTROL_PRECISE_BIT"
        showsPrec Int
p (VkQueryControlBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkQueryControlBitmask " 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 (VkQueryControlBitmask a) where
        readPrec :: ReadPrec (VkQueryControlBitmask a)
readPrec
          = ReadPrec (VkQueryControlBitmask a)
-> ReadPrec (VkQueryControlBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkQueryControlBitmask a))]
-> ReadPrec (VkQueryControlBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_QUERY_CONTROL_PRECISE_BIT",
                   VkQueryControlBitmask a -> ReadPrec (VkQueryControlBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryControlBitmask a
forall (a :: FlagType). VkQueryControlBitmask a
VK_QUERY_CONTROL_PRECISE_BIT)]
                 ReadPrec (VkQueryControlBitmask a)
-> ReadPrec (VkQueryControlBitmask a)
-> ReadPrec (VkQueryControlBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkQueryControlBitmask a)
-> ReadPrec (VkQueryControlBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueryControlBitmask") ReadPrec ()
-> ReadPrec (VkQueryControlBitmask a)
-> ReadPrec (VkQueryControlBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkQueryControlBitmask a
forall (a :: FlagType). VkFlags -> VkQueryControlBitmask a
VkQueryControlBitmask (VkFlags -> VkQueryControlBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkQueryControlBitmask 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)))

-- | Require precise results to be collected by the query
--
--   bitpos = @0@
pattern VK_QUERY_CONTROL_PRECISE_BIT :: VkQueryControlBitmask a

pattern $bVK_QUERY_CONTROL_PRECISE_BIT :: VkQueryControlBitmask a
$mVK_QUERY_CONTROL_PRECISE_BIT :: forall r (a :: FlagType).
VkQueryControlBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_CONTROL_PRECISE_BIT = VkQueryControlBitmask 1

newtype VkQueryPipelineStatisticBitmask (a ::
                                           FlagType) = VkQueryPipelineStatisticBitmask VkFlags
                                                         deriving (VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
(VkQueryPipelineStatisticBitmask a
 -> VkQueryPipelineStatisticBitmask a -> Bool)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Bool)
-> Eq (VkQueryPipelineStatisticBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
/= :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
== :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
Eq, Eq (VkQueryPipelineStatisticBitmask a)
Eq (VkQueryPipelineStatisticBitmask a)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Ordering)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Bool)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Bool)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Bool)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a -> Bool)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a)
-> (VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a)
-> Ord (VkQueryPipelineStatisticBitmask a)
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Ordering
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask 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 (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Ordering
forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
min :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
$cmin :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
max :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
$cmax :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
>= :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
> :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
<= :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
< :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Bool
compare :: VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkQueryPipelineStatisticBitmask a)
Ord, Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a)
Ptr b -> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
Ptr (VkQueryPipelineStatisticBitmask a)
-> IO (VkQueryPipelineStatisticBitmask a)
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> IO (VkQueryPipelineStatisticBitmask a)
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
Ptr (VkQueryPipelineStatisticBitmask a)
-> VkQueryPipelineStatisticBitmask a -> IO ()
VkQueryPipelineStatisticBitmask a -> Int
(VkQueryPipelineStatisticBitmask a -> Int)
-> (VkQueryPipelineStatisticBitmask a -> Int)
-> (Ptr (VkQueryPipelineStatisticBitmask a)
    -> Int -> IO (VkQueryPipelineStatisticBitmask a))
-> (Ptr (VkQueryPipelineStatisticBitmask a)
    -> Int -> VkQueryPipelineStatisticBitmask a -> IO ())
-> (forall b.
    Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a))
-> (forall b.
    Ptr b -> Int -> VkQueryPipelineStatisticBitmask a -> IO ())
-> (Ptr (VkQueryPipelineStatisticBitmask a)
    -> IO (VkQueryPipelineStatisticBitmask a))
-> (Ptr (VkQueryPipelineStatisticBitmask a)
    -> VkQueryPipelineStatisticBitmask a -> IO ())
-> Storable (VkQueryPipelineStatisticBitmask a)
forall b. Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a)
forall b.
Ptr b -> Int -> VkQueryPipelineStatisticBitmask 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 (VkQueryPipelineStatisticBitmask a)
-> IO (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> IO (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> VkQueryPipelineStatisticBitmask a -> IO ()
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
poke :: Ptr (VkQueryPipelineStatisticBitmask a)
-> VkQueryPipelineStatisticBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> VkQueryPipelineStatisticBitmask a -> IO ()
peek :: Ptr (VkQueryPipelineStatisticBitmask a)
-> IO (VkQueryPipelineStatisticBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> IO (VkQueryPipelineStatisticBitmask a)
pokeByteOff :: Ptr b -> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryPipelineStatisticBitmask a)
pokeElemOff :: Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> VkQueryPipelineStatisticBitmask a -> IO ()
peekElemOff :: Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> IO (VkQueryPipelineStatisticBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkQueryPipelineStatisticBitmask a)
-> Int -> IO (VkQueryPipelineStatisticBitmask a)
alignment :: VkQueryPipelineStatisticBitmask a -> Int
$calignment :: forall (a :: FlagType). VkQueryPipelineStatisticBitmask a -> Int
sizeOf :: VkQueryPipelineStatisticBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkQueryPipelineStatisticBitmask a -> Int
Storable, Typeable (VkQueryPipelineStatisticBitmask a)
DataType
Constr
Typeable (VkQueryPipelineStatisticBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkQueryPipelineStatisticBitmask a
    -> c (VkQueryPipelineStatisticBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r)
    -> Constr
    -> c (VkQueryPipelineStatisticBitmask a))
-> (VkQueryPipelineStatisticBitmask a -> Constr)
-> (VkQueryPipelineStatisticBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkQueryPipelineStatisticBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkQueryPipelineStatisticBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkQueryPipelineStatisticBitmask a
    -> VkQueryPipelineStatisticBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryPipelineStatisticBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryPipelineStatisticBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u)
    -> VkQueryPipelineStatisticBitmask a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u)
    -> VkQueryPipelineStatisticBitmask a
    -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPipelineStatisticBitmask a
    -> m (VkQueryPipelineStatisticBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPipelineStatisticBitmask a
    -> m (VkQueryPipelineStatisticBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPipelineStatisticBitmask a
    -> m (VkQueryPipelineStatisticBitmask a))
-> Data (VkQueryPipelineStatisticBitmask a)
VkQueryPipelineStatisticBitmask a -> DataType
VkQueryPipelineStatisticBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPipelineStatisticBitmask a
-> c (VkQueryPipelineStatisticBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (VkQueryPipelineStatisticBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a
-> u
forall u.
(forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType).
Typeable a =>
VkQueryPipelineStatisticBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkQueryPipelineStatisticBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a
-> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPipelineStatisticBitmask a
-> c (VkQueryPipelineStatisticBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (VkQueryPipelineStatisticBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPipelineStatisticBitmask a
-> c (VkQueryPipelineStatisticBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
$cVkQueryPipelineStatisticBitmask :: Constr
$tVkQueryPipelineStatisticBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryPipelineStatisticBitmask a
-> m (VkQueryPipelineStatisticBitmask a)
gmapQi :: Int
-> (forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a
-> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a
-> u
gmapQ :: (forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u)
-> VkQueryPipelineStatisticBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPipelineStatisticBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryPipelineStatisticBitmask a
-> VkQueryPipelineStatisticBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkQueryPipelineStatisticBitmask a))
dataTypeOf :: VkQueryPipelineStatisticBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkQueryPipelineStatisticBitmask a -> DataType
toConstr :: VkQueryPipelineStatisticBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkQueryPipelineStatisticBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (VkQueryPipelineStatisticBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (VkQueryPipelineStatisticBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPipelineStatisticBitmask a
-> c (VkQueryPipelineStatisticBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPipelineStatisticBitmask a
-> c (VkQueryPipelineStatisticBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryPipelineStatisticBitmask a)
Data, (forall x.
 VkQueryPipelineStatisticBitmask a
 -> Rep (VkQueryPipelineStatisticBitmask a) x)
-> (forall x.
    Rep (VkQueryPipelineStatisticBitmask a) x
    -> VkQueryPipelineStatisticBitmask a)
-> Generic (VkQueryPipelineStatisticBitmask a)
forall x.
Rep (VkQueryPipelineStatisticBitmask a) x
-> VkQueryPipelineStatisticBitmask a
forall x.
VkQueryPipelineStatisticBitmask a
-> Rep (VkQueryPipelineStatisticBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkQueryPipelineStatisticBitmask a) x
-> VkQueryPipelineStatisticBitmask a
forall (a :: FlagType) x.
VkQueryPipelineStatisticBitmask a
-> Rep (VkQueryPipelineStatisticBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkQueryPipelineStatisticBitmask a) x
-> VkQueryPipelineStatisticBitmask a
$cfrom :: forall (a :: FlagType) x.
VkQueryPipelineStatisticBitmask a
-> Rep (VkQueryPipelineStatisticBitmask a) x
Generic)

type VkQueryPipelineStatisticFlags =
     VkQueryPipelineStatisticBitmask FlagMask

type VkQueryPipelineStatisticFlagBits =
     VkQueryPipelineStatisticBitmask FlagBit

pattern VkQueryPipelineStatisticFlagBits ::
        VkFlags -> VkQueryPipelineStatisticBitmask FlagBit

pattern $bVkQueryPipelineStatisticFlagBits :: VkFlags -> VkQueryPipelineStatisticBitmask FlagBit
$mVkQueryPipelineStatisticFlagBits :: forall r.
VkQueryPipelineStatisticBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryPipelineStatisticFlagBits n =
        VkQueryPipelineStatisticBitmask n

pattern VkQueryPipelineStatisticFlags ::
        VkFlags -> VkQueryPipelineStatisticBitmask FlagMask

pattern $bVkQueryPipelineStatisticFlags :: VkFlags -> VkQueryPipelineStatisticBitmask FlagMask
$mVkQueryPipelineStatisticFlags :: forall r.
VkQueryPipelineStatisticBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryPipelineStatisticFlags n =
        VkQueryPipelineStatisticBitmask n

deriving instance Bits (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance
         FiniteBits (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance
         Integral (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance Num (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance
         Bounded (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance Enum (VkQueryPipelineStatisticBitmask FlagMask)

deriving instance Real (VkQueryPipelineStatisticBitmask FlagMask)

instance Show (VkQueryPipelineStatisticBitmask a) where
        showsPrec :: Int -> VkQueryPipelineStatisticBitmask a -> ShowS
showsPrec Int
_ VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT"
        showsPrec Int
_ VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT
          = String -> ShowS
showString String
"VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT"
        showsPrec Int
_ VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT
          = String -> ShowS
showString String
"VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT"
        showsPrec Int
_
          VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT
          = String -> ShowS
showString
              String
"VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT"
        showsPrec Int
p (VkQueryPipelineStatisticBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkQueryPipelineStatisticBitmask " 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 (VkQueryPipelineStatisticBitmask a) where
        readPrec :: ReadPrec (VkQueryPipelineStatisticBitmask a)
readPrec
          = ReadPrec (VkQueryPipelineStatisticBitmask a)
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkQueryPipelineStatisticBitmask a))]
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
                     VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
                     VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT),
                  (String
"VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT",
                   VkQueryPipelineStatisticBitmask a
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryPipelineStatisticBitmask a
forall (a :: FlagType). VkQueryPipelineStatisticBitmask a
VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT)]
                 ReadPrec (VkQueryPipelineStatisticBitmask a)
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueryPipelineStatisticBitmask") ReadPrec ()
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
-> ReadPrec (VkQueryPipelineStatisticBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkQueryPipelineStatisticBitmask a
forall (a :: FlagType).
VkFlags -> VkQueryPipelineStatisticBitmask a
VkQueryPipelineStatisticBitmask (VkFlags -> VkQueryPipelineStatisticBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkQueryPipelineStatisticBitmask 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)))

-- | Optional
--
--   bitpos = @0@
pattern VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT ::
        VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_VERTICES_BIT =
        VkQueryPipelineStatisticBitmask 1

-- | Optional
--
--   bitpos = @1@
pattern VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_INPUT_ASSEMBLY_PRIMITIVES_BIT =
        VkQueryPipelineStatisticBitmask 2

-- | Optional
--
--   bitpos = @2@
pattern VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_VERTEX_SHADER_INVOCATIONS_BIT =
        VkQueryPipelineStatisticBitmask 4

-- | Optional
--
--   bitpos = @3@
pattern VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_INVOCATIONS_BIT
        = VkQueryPipelineStatisticBitmask 8

-- | Optional
--
--   bitpos = @4@
pattern VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_GEOMETRY_SHADER_PRIMITIVES_BIT
        = VkQueryPipelineStatisticBitmask 16

-- | Optional
--
--   bitpos = @5@
pattern VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT ::
        VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_INVOCATIONS_BIT =
        VkQueryPipelineStatisticBitmask 32

-- | Optional
--
--   bitpos = @6@
pattern VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT ::
        VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_CLIPPING_PRIMITIVES_BIT =
        VkQueryPipelineStatisticBitmask 64

-- | Optional
--
--   bitpos = @7@
pattern VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_FRAGMENT_SHADER_INVOCATIONS_BIT
        = VkQueryPipelineStatisticBitmask 128

-- | Optional
--
--   bitpos = @8@
pattern VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_CONTROL_SHADER_PATCHES_BIT
        = VkQueryPipelineStatisticBitmask 256

-- | Optional
--
--   bitpos = @9@
pattern VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_TESSELLATION_EVALUATION_SHADER_INVOCATIONS_BIT
        = VkQueryPipelineStatisticBitmask 512

-- | Optional
--
--   bitpos = @10@
pattern VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT
        :: VkQueryPipelineStatisticBitmask a

pattern $bVK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT :: VkQueryPipelineStatisticBitmask a
$mVK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT :: forall r (a :: FlagType).
VkQueryPipelineStatisticBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_PIPELINE_STATISTIC_COMPUTE_SHADER_INVOCATIONS_BIT
        = VkQueryPipelineStatisticBitmask 1024

newtype VkQueryPoolCreateFlagBits = VkQueryPoolCreateFlagBits VkFlags
                                      deriving (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
(VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> Eq VkQueryPoolCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c/= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
== :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c== :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
Eq, Eq VkQueryPoolCreateFlagBits
Eq VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> Ordering)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> Ord VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Ordering
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
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 :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cmin :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
max :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cmax :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
>= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c>= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
> :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c> :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
<= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c<= :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
< :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
$c< :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Bool
compare :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Ordering
$ccompare :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> Ordering
$cp1Ord :: Eq VkQueryPoolCreateFlagBits
Ord, Integer -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
(VkQueryPoolCreateFlagBits
 -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (Integer -> VkQueryPoolCreateFlagBits)
-> Num VkQueryPoolCreateFlagBits
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkQueryPoolCreateFlagBits
$cfromInteger :: Integer -> VkQueryPoolCreateFlagBits
signum :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$csignum :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
abs :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cabs :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
negate :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cnegate :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
* :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$c* :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
- :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$c- :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
+ :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$c+ :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
Num, VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> Bounded VkQueryPoolCreateFlagBits
forall a. a -> a -> Bounded a
maxBound :: VkQueryPoolCreateFlagBits
$cmaxBound :: VkQueryPoolCreateFlagBits
minBound :: VkQueryPoolCreateFlagBits
$cminBound :: VkQueryPoolCreateFlagBits
Bounded, Int -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Int
VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> [VkQueryPoolCreateFlagBits]
(VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int)
-> (VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits])
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits])
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits])
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits
    -> [VkQueryPoolCreateFlagBits])
-> Enum VkQueryPoolCreateFlagBits
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 :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> [VkQueryPoolCreateFlagBits]
$cenumFromThenTo :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> [VkQueryPoolCreateFlagBits]
enumFromTo :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
$cenumFromTo :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
enumFromThen :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
$cenumFromThen :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
enumFrom :: VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
$cenumFrom :: VkQueryPoolCreateFlagBits -> [VkQueryPoolCreateFlagBits]
fromEnum :: VkQueryPoolCreateFlagBits -> Int
$cfromEnum :: VkQueryPoolCreateFlagBits -> Int
toEnum :: Int -> VkQueryPoolCreateFlagBits
$ctoEnum :: Int -> VkQueryPoolCreateFlagBits
pred :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cpred :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
succ :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$csucc :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
Enum, Enum VkQueryPoolCreateFlagBits
Real VkQueryPoolCreateFlagBits
Real VkQueryPoolCreateFlagBits
-> Enum VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits
    -> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits))
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits
    -> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits))
-> (VkQueryPoolCreateFlagBits -> Integer)
-> Integral VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Integer
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits)
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: VkQueryPoolCreateFlagBits -> Integer
$ctoInteger :: VkQueryPoolCreateFlagBits -> Integer
divMod :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits)
$cdivMod :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits)
quotRem :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits)
$cquotRem :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits, VkQueryPoolCreateFlagBits)
mod :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cmod :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
div :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cdiv :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
rem :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$crem :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
quot :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cquot :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cp2Integral :: Enum VkQueryPoolCreateFlagBits
$cp1Integral :: Real VkQueryPoolCreateFlagBits
Integral, Eq VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits
Eq VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> VkQueryPoolCreateFlagBits
-> (Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> Bool)
-> (VkQueryPoolCreateFlagBits -> Maybe Int)
-> (VkQueryPoolCreateFlagBits -> Int)
-> (VkQueryPoolCreateFlagBits -> Bool)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Int)
-> Bits VkQueryPoolCreateFlagBits
Int -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Bool
VkQueryPoolCreateFlagBits -> Int
VkQueryPoolCreateFlagBits -> Maybe Int
VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Int -> Bool
VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
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 :: VkQueryPoolCreateFlagBits -> Int
$cpopCount :: VkQueryPoolCreateFlagBits -> Int
rotateR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$crotateR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
rotateL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$crotateL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
unsafeShiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cunsafeShiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
shiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cshiftR :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
unsafeShiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cunsafeShiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
shiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cshiftL :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
isSigned :: VkQueryPoolCreateFlagBits -> Bool
$cisSigned :: VkQueryPoolCreateFlagBits -> Bool
bitSize :: VkQueryPoolCreateFlagBits -> Int
$cbitSize :: VkQueryPoolCreateFlagBits -> Int
bitSizeMaybe :: VkQueryPoolCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: VkQueryPoolCreateFlagBits -> Maybe Int
testBit :: VkQueryPoolCreateFlagBits -> Int -> Bool
$ctestBit :: VkQueryPoolCreateFlagBits -> Int -> Bool
complementBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$ccomplementBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
clearBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cclearBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
setBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$csetBit :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
bit :: Int -> VkQueryPoolCreateFlagBits
$cbit :: Int -> VkQueryPoolCreateFlagBits
zeroBits :: VkQueryPoolCreateFlagBits
$czeroBits :: VkQueryPoolCreateFlagBits
rotate :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$crotate :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
shift :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
$cshift :: VkQueryPoolCreateFlagBits -> Int -> VkQueryPoolCreateFlagBits
complement :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$ccomplement :: VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
xor :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cxor :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
.|. :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$c.|. :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
.&. :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$c.&. :: VkQueryPoolCreateFlagBits
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cp1Bits :: Eq VkQueryPoolCreateFlagBits
Bits,
                                                Bits VkQueryPoolCreateFlagBits
Bits VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits -> Int)
-> (VkQueryPoolCreateFlagBits -> Int)
-> (VkQueryPoolCreateFlagBits -> Int)
-> FiniteBits VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkQueryPoolCreateFlagBits -> Int
$ccountTrailingZeros :: VkQueryPoolCreateFlagBits -> Int
countLeadingZeros :: VkQueryPoolCreateFlagBits -> Int
$ccountLeadingZeros :: VkQueryPoolCreateFlagBits -> Int
finiteBitSize :: VkQueryPoolCreateFlagBits -> Int
$cfiniteBitSize :: VkQueryPoolCreateFlagBits -> Int
$cp1FiniteBits :: Bits VkQueryPoolCreateFlagBits
FiniteBits, Ptr b -> Int -> IO VkQueryPoolCreateFlagBits
Ptr b -> Int -> VkQueryPoolCreateFlagBits -> IO ()
Ptr VkQueryPoolCreateFlagBits -> IO VkQueryPoolCreateFlagBits
Ptr VkQueryPoolCreateFlagBits
-> Int -> IO VkQueryPoolCreateFlagBits
Ptr VkQueryPoolCreateFlagBits
-> Int -> VkQueryPoolCreateFlagBits -> IO ()
Ptr VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> IO ()
VkQueryPoolCreateFlagBits -> Int
(VkQueryPoolCreateFlagBits -> Int)
-> (VkQueryPoolCreateFlagBits -> Int)
-> (Ptr VkQueryPoolCreateFlagBits
    -> Int -> IO VkQueryPoolCreateFlagBits)
-> (Ptr VkQueryPoolCreateFlagBits
    -> Int -> VkQueryPoolCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO VkQueryPoolCreateFlagBits)
-> (forall b. Ptr b -> Int -> VkQueryPoolCreateFlagBits -> IO ())
-> (Ptr VkQueryPoolCreateFlagBits -> IO VkQueryPoolCreateFlagBits)
-> (Ptr VkQueryPoolCreateFlagBits
    -> VkQueryPoolCreateFlagBits -> IO ())
-> Storable VkQueryPoolCreateFlagBits
forall b. Ptr b -> Int -> IO VkQueryPoolCreateFlagBits
forall b. Ptr b -> Int -> VkQueryPoolCreateFlagBits -> 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 VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> IO ()
$cpoke :: Ptr VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits -> IO ()
peek :: Ptr VkQueryPoolCreateFlagBits -> IO VkQueryPoolCreateFlagBits
$cpeek :: Ptr VkQueryPoolCreateFlagBits -> IO VkQueryPoolCreateFlagBits
pokeByteOff :: Ptr b -> Int -> VkQueryPoolCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkQueryPoolCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkQueryPoolCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkQueryPoolCreateFlagBits
pokeElemOff :: Ptr VkQueryPoolCreateFlagBits
-> Int -> VkQueryPoolCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr VkQueryPoolCreateFlagBits
-> Int -> VkQueryPoolCreateFlagBits -> IO ()
peekElemOff :: Ptr VkQueryPoolCreateFlagBits
-> Int -> IO VkQueryPoolCreateFlagBits
$cpeekElemOff :: Ptr VkQueryPoolCreateFlagBits
-> Int -> IO VkQueryPoolCreateFlagBits
alignment :: VkQueryPoolCreateFlagBits -> Int
$calignment :: VkQueryPoolCreateFlagBits -> Int
sizeOf :: VkQueryPoolCreateFlagBits -> Int
$csizeOf :: VkQueryPoolCreateFlagBits -> Int
Storable, Num VkQueryPoolCreateFlagBits
Ord VkQueryPoolCreateFlagBits
Num VkQueryPoolCreateFlagBits
-> Ord VkQueryPoolCreateFlagBits
-> (VkQueryPoolCreateFlagBits -> Rational)
-> Real VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: VkQueryPoolCreateFlagBits -> Rational
$ctoRational :: VkQueryPoolCreateFlagBits -> Rational
$cp2Real :: Ord VkQueryPoolCreateFlagBits
$cp1Real :: Num VkQueryPoolCreateFlagBits
Real, Typeable VkQueryPoolCreateFlagBits
DataType
Constr
Typeable VkQueryPoolCreateFlagBits
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkQueryPoolCreateFlagBits
    -> c VkQueryPoolCreateFlagBits)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits)
-> (VkQueryPoolCreateFlagBits -> Constr)
-> (VkQueryPoolCreateFlagBits -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c VkQueryPoolCreateFlagBits))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkQueryPoolCreateFlagBits))
-> ((forall b. Data b => b -> b)
    -> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryPoolCreateFlagBits
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryPoolCreateFlagBits
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits)
-> Data VkQueryPoolCreateFlagBits
VkQueryPoolCreateFlagBits -> DataType
VkQueryPoolCreateFlagBits -> Constr
(forall b. Data b => b -> b)
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPoolCreateFlagBits
-> c VkQueryPoolCreateFlagBits
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> u
forall u.
(forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPoolCreateFlagBits
-> c VkQueryPoolCreateFlagBits
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c VkQueryPoolCreateFlagBits)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryPoolCreateFlagBits)
$cVkQueryPoolCreateFlagBits :: Constr
$tVkQueryPoolCreateFlagBits :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
gmapM :: (forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueryPoolCreateFlagBits -> m VkQueryPoolCreateFlagBits
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> VkQueryPoolCreateFlagBits -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryPoolCreateFlagBits
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
$cgmapT :: (forall b. Data b => b -> b)
-> VkQueryPoolCreateFlagBits -> VkQueryPoolCreateFlagBits
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryPoolCreateFlagBits)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryPoolCreateFlagBits)
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c VkQueryPoolCreateFlagBits)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c VkQueryPoolCreateFlagBits)
dataTypeOf :: VkQueryPoolCreateFlagBits -> DataType
$cdataTypeOf :: VkQueryPoolCreateFlagBits -> DataType
toConstr :: VkQueryPoolCreateFlagBits -> Constr
$ctoConstr :: VkQueryPoolCreateFlagBits -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryPoolCreateFlagBits
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPoolCreateFlagBits
-> c VkQueryPoolCreateFlagBits
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryPoolCreateFlagBits
-> c VkQueryPoolCreateFlagBits
$cp1Data :: Typeable VkQueryPoolCreateFlagBits
Data, (forall x.
 VkQueryPoolCreateFlagBits -> Rep VkQueryPoolCreateFlagBits x)
-> (forall x.
    Rep VkQueryPoolCreateFlagBits x -> VkQueryPoolCreateFlagBits)
-> Generic VkQueryPoolCreateFlagBits
forall x.
Rep VkQueryPoolCreateFlagBits x -> VkQueryPoolCreateFlagBits
forall x.
VkQueryPoolCreateFlagBits -> Rep VkQueryPoolCreateFlagBits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VkQueryPoolCreateFlagBits x -> VkQueryPoolCreateFlagBits
$cfrom :: forall x.
VkQueryPoolCreateFlagBits -> Rep VkQueryPoolCreateFlagBits x
Generic)

instance Show VkQueryPoolCreateFlagBits where
        {-# INLINE show #-}
        show :: VkQueryPoolCreateFlagBits -> String
show (VkQueryPoolCreateFlagBits VkFlags
x) = VkFlags -> String
forall a. Show a => a -> String
show VkFlags
x

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

newtype VkQueryResultBitmask (a ::
                                FlagType) = VkQueryResultBitmask VkFlags
                                              deriving (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
(VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> Eq (VkQueryResultBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
/= :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
== :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
Eq, Eq (VkQueryResultBitmask a)
Eq (VkQueryResultBitmask a)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Ordering)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> (VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool)
-> (VkQueryResultBitmask a
    -> VkQueryResultBitmask a -> VkQueryResultBitmask a)
-> (VkQueryResultBitmask a
    -> VkQueryResultBitmask a -> VkQueryResultBitmask a)
-> Ord (VkQueryResultBitmask a)
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Ordering
VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask 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 (VkQueryResultBitmask a)
forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Ordering
forall (a :: FlagType).
VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
min :: VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
$cmin :: forall (a :: FlagType).
VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
max :: VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
$cmax :: forall (a :: FlagType).
VkQueryResultBitmask a
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
>= :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
> :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
<= :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
< :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Bool
compare :: VkQueryResultBitmask a -> VkQueryResultBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkQueryResultBitmask a -> VkQueryResultBitmask a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkQueryResultBitmask a)
Ord, Ptr b -> Int -> IO (VkQueryResultBitmask a)
Ptr b -> Int -> VkQueryResultBitmask a -> IO ()
Ptr (VkQueryResultBitmask a) -> IO (VkQueryResultBitmask a)
Ptr (VkQueryResultBitmask a) -> Int -> IO (VkQueryResultBitmask a)
Ptr (VkQueryResultBitmask a)
-> Int -> VkQueryResultBitmask a -> IO ()
Ptr (VkQueryResultBitmask a) -> VkQueryResultBitmask a -> IO ()
VkQueryResultBitmask a -> Int
(VkQueryResultBitmask a -> Int)
-> (VkQueryResultBitmask a -> Int)
-> (Ptr (VkQueryResultBitmask a)
    -> Int -> IO (VkQueryResultBitmask a))
-> (Ptr (VkQueryResultBitmask a)
    -> Int -> VkQueryResultBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkQueryResultBitmask a))
-> (forall b. Ptr b -> Int -> VkQueryResultBitmask a -> IO ())
-> (Ptr (VkQueryResultBitmask a) -> IO (VkQueryResultBitmask a))
-> (Ptr (VkQueryResultBitmask a)
    -> VkQueryResultBitmask a -> IO ())
-> Storable (VkQueryResultBitmask a)
forall b. Ptr b -> Int -> IO (VkQueryResultBitmask a)
forall b. Ptr b -> Int -> VkQueryResultBitmask 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 (VkQueryResultBitmask a) -> IO (VkQueryResultBitmask a)
forall (a :: FlagType).
Ptr (VkQueryResultBitmask a) -> Int -> IO (VkQueryResultBitmask a)
forall (a :: FlagType).
Ptr (VkQueryResultBitmask a)
-> Int -> VkQueryResultBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkQueryResultBitmask a) -> VkQueryResultBitmask a -> IO ()
forall (a :: FlagType). VkQueryResultBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryResultBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryResultBitmask a -> IO ()
poke :: Ptr (VkQueryResultBitmask a) -> VkQueryResultBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkQueryResultBitmask a) -> VkQueryResultBitmask a -> IO ()
peek :: Ptr (VkQueryResultBitmask a) -> IO (VkQueryResultBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkQueryResultBitmask a) -> IO (VkQueryResultBitmask a)
pokeByteOff :: Ptr b -> Int -> VkQueryResultBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkQueryResultBitmask a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkQueryResultBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkQueryResultBitmask a)
pokeElemOff :: Ptr (VkQueryResultBitmask a)
-> Int -> VkQueryResultBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkQueryResultBitmask a)
-> Int -> VkQueryResultBitmask a -> IO ()
peekElemOff :: Ptr (VkQueryResultBitmask a) -> Int -> IO (VkQueryResultBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkQueryResultBitmask a) -> Int -> IO (VkQueryResultBitmask a)
alignment :: VkQueryResultBitmask a -> Int
$calignment :: forall (a :: FlagType). VkQueryResultBitmask a -> Int
sizeOf :: VkQueryResultBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkQueryResultBitmask a -> Int
Storable, Typeable (VkQueryResultBitmask a)
DataType
Constr
Typeable (VkQueryResultBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkQueryResultBitmask a
    -> c (VkQueryResultBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a))
-> (VkQueryResultBitmask a -> Constr)
-> (VkQueryResultBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkQueryResultBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkQueryResultBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkQueryResultBitmask a -> VkQueryResultBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryResultBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkQueryResultBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkQueryResultBitmask a -> m (VkQueryResultBitmask a))
-> Data (VkQueryResultBitmask a)
VkQueryResultBitmask a -> DataType
VkQueryResultBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryResultBitmask a
-> c (VkQueryResultBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryResultBitmask a)
forall (a :: FlagType).
Typeable a =>
VkQueryResultBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkQueryResultBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryResultBitmask a
-> c (VkQueryResultBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueryResultBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryResultBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryResultBitmask a
-> c (VkQueryResultBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueryResultBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryResultBitmask a))
$cVkQueryResultBitmask :: Constr
$tVkQueryResultBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueryResultBitmask a -> m (VkQueryResultBitmask a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueryResultBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueryResultBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueryResultBitmask a -> VkQueryResultBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryResultBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueryResultBitmask a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (VkQueryResultBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueryResultBitmask a))
dataTypeOf :: VkQueryResultBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkQueryResultBitmask a -> DataType
toConstr :: VkQueryResultBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkQueryResultBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueryResultBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryResultBitmask a
-> c (VkQueryResultBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueryResultBitmask a
-> c (VkQueryResultBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkQueryResultBitmask a)
Data, (forall x.
 VkQueryResultBitmask a -> Rep (VkQueryResultBitmask a) x)
-> (forall x.
    Rep (VkQueryResultBitmask a) x -> VkQueryResultBitmask a)
-> Generic (VkQueryResultBitmask a)
forall x. Rep (VkQueryResultBitmask a) x -> VkQueryResultBitmask a
forall x. VkQueryResultBitmask a -> Rep (VkQueryResultBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkQueryResultBitmask a) x -> VkQueryResultBitmask a
forall (a :: FlagType) x.
VkQueryResultBitmask a -> Rep (VkQueryResultBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkQueryResultBitmask a) x -> VkQueryResultBitmask a
$cfrom :: forall (a :: FlagType) x.
VkQueryResultBitmask a -> Rep (VkQueryResultBitmask a) x
Generic)

type VkQueryResultFlags = VkQueryResultBitmask FlagMask

type VkQueryResultFlagBits = VkQueryResultBitmask FlagBit

pattern VkQueryResultFlagBits ::
        VkFlags -> VkQueryResultBitmask FlagBit

pattern $bVkQueryResultFlagBits :: VkFlags -> VkQueryResultBitmask FlagBit
$mVkQueryResultFlagBits :: forall r.
VkQueryResultBitmask FlagBit -> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryResultFlagBits n = VkQueryResultBitmask n

pattern VkQueryResultFlags ::
        VkFlags -> VkQueryResultBitmask FlagMask

pattern $bVkQueryResultFlags :: VkFlags -> VkQueryResultBitmask FlagMask
$mVkQueryResultFlags :: forall r.
VkQueryResultBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkQueryResultFlags n = VkQueryResultBitmask n

deriving instance Bits (VkQueryResultBitmask FlagMask)

deriving instance FiniteBits (VkQueryResultBitmask FlagMask)

deriving instance Integral (VkQueryResultBitmask FlagMask)

deriving instance Num (VkQueryResultBitmask FlagMask)

deriving instance Bounded (VkQueryResultBitmask FlagMask)

deriving instance Enum (VkQueryResultBitmask FlagMask)

deriving instance Real (VkQueryResultBitmask FlagMask)

instance Show (VkQueryResultBitmask a) where
        showsPrec :: Int -> VkQueryResultBitmask a -> ShowS
showsPrec Int
_ VkQueryResultBitmask a
VK_QUERY_RESULT_64_BIT
          = String -> ShowS
showString String
"VK_QUERY_RESULT_64_BIT"
        showsPrec Int
_ VkQueryResultBitmask a
VK_QUERY_RESULT_WAIT_BIT
          = String -> ShowS
showString String
"VK_QUERY_RESULT_WAIT_BIT"
        showsPrec Int
_ VkQueryResultBitmask a
VK_QUERY_RESULT_WITH_AVAILABILITY_BIT
          = String -> ShowS
showString String
"VK_QUERY_RESULT_WITH_AVAILABILITY_BIT"
        showsPrec Int
_ VkQueryResultBitmask a
VK_QUERY_RESULT_PARTIAL_BIT
          = String -> ShowS
showString String
"VK_QUERY_RESULT_PARTIAL_BIT"
        showsPrec Int
p (VkQueryResultBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkQueryResultBitmask " 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 (VkQueryResultBitmask a) where
        readPrec :: ReadPrec (VkQueryResultBitmask a)
readPrec
          = ReadPrec (VkQueryResultBitmask a)
-> ReadPrec (VkQueryResultBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkQueryResultBitmask a))]
-> ReadPrec (VkQueryResultBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_QUERY_RESULT_64_BIT", VkQueryResultBitmask a -> ReadPrec (VkQueryResultBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryResultBitmask a
forall (a :: FlagType). VkQueryResultBitmask a
VK_QUERY_RESULT_64_BIT),
                  (String
"VK_QUERY_RESULT_WAIT_BIT", VkQueryResultBitmask a -> ReadPrec (VkQueryResultBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryResultBitmask a
forall (a :: FlagType). VkQueryResultBitmask a
VK_QUERY_RESULT_WAIT_BIT),
                  (String
"VK_QUERY_RESULT_WITH_AVAILABILITY_BIT",
                   VkQueryResultBitmask a -> ReadPrec (VkQueryResultBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryResultBitmask a
forall (a :: FlagType). VkQueryResultBitmask a
VK_QUERY_RESULT_WITH_AVAILABILITY_BIT),
                  (String
"VK_QUERY_RESULT_PARTIAL_BIT", VkQueryResultBitmask a -> ReadPrec (VkQueryResultBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryResultBitmask a
forall (a :: FlagType). VkQueryResultBitmask a
VK_QUERY_RESULT_PARTIAL_BIT)]
                 ReadPrec (VkQueryResultBitmask a)
-> ReadPrec (VkQueryResultBitmask a)
-> ReadPrec (VkQueryResultBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkQueryResultBitmask a)
-> ReadPrec (VkQueryResultBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueryResultBitmask") ReadPrec ()
-> ReadPrec (VkQueryResultBitmask a)
-> ReadPrec (VkQueryResultBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkQueryResultBitmask a
forall (a :: FlagType). VkFlags -> VkQueryResultBitmask a
VkQueryResultBitmask (VkFlags -> VkQueryResultBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkQueryResultBitmask 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)))

-- | Results of the queries are written to the destination buffer as 64-bit values
--
--   bitpos = @0@
pattern VK_QUERY_RESULT_64_BIT :: VkQueryResultBitmask a

pattern $bVK_QUERY_RESULT_64_BIT :: VkQueryResultBitmask a
$mVK_QUERY_RESULT_64_BIT :: forall r (a :: FlagType).
VkQueryResultBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_RESULT_64_BIT = VkQueryResultBitmask 1

-- | Results of the queries are waited on before proceeding with the result copy
--
--   bitpos = @1@
pattern VK_QUERY_RESULT_WAIT_BIT :: VkQueryResultBitmask a

pattern $bVK_QUERY_RESULT_WAIT_BIT :: VkQueryResultBitmask a
$mVK_QUERY_RESULT_WAIT_BIT :: forall r (a :: FlagType).
VkQueryResultBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_RESULT_WAIT_BIT = VkQueryResultBitmask 2

-- | Besides the results of the query, the availability of the results is also written
--
--   bitpos = @2@
pattern VK_QUERY_RESULT_WITH_AVAILABILITY_BIT ::
        VkQueryResultBitmask a

pattern $bVK_QUERY_RESULT_WITH_AVAILABILITY_BIT :: VkQueryResultBitmask a
$mVK_QUERY_RESULT_WITH_AVAILABILITY_BIT :: forall r (a :: FlagType).
VkQueryResultBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_RESULT_WITH_AVAILABILITY_BIT =
        VkQueryResultBitmask 4

-- | Copy the partial results of the query even if the final results are not available
--
--   bitpos = @3@
pattern VK_QUERY_RESULT_PARTIAL_BIT :: VkQueryResultBitmask a

pattern $bVK_QUERY_RESULT_PARTIAL_BIT :: VkQueryResultBitmask a
$mVK_QUERY_RESULT_PARTIAL_BIT :: forall r (a :: FlagType).
VkQueryResultBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_RESULT_PARTIAL_BIT = VkQueryResultBitmask 8

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkQueryType VkQueryType registry at www.khronos.org>
newtype VkQueryType = VkQueryType Int32
                        deriving (VkQueryType -> VkQueryType -> Bool
(VkQueryType -> VkQueryType -> Bool)
-> (VkQueryType -> VkQueryType -> Bool) -> Eq VkQueryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkQueryType -> VkQueryType -> Bool
$c/= :: VkQueryType -> VkQueryType -> Bool
== :: VkQueryType -> VkQueryType -> Bool
$c== :: VkQueryType -> VkQueryType -> Bool
Eq, Eq VkQueryType
Eq VkQueryType
-> (VkQueryType -> VkQueryType -> Ordering)
-> (VkQueryType -> VkQueryType -> Bool)
-> (VkQueryType -> VkQueryType -> Bool)
-> (VkQueryType -> VkQueryType -> Bool)
-> (VkQueryType -> VkQueryType -> Bool)
-> (VkQueryType -> VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType -> VkQueryType)
-> Ord VkQueryType
VkQueryType -> VkQueryType -> Bool
VkQueryType -> VkQueryType -> Ordering
VkQueryType -> VkQueryType -> VkQueryType
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 :: VkQueryType -> VkQueryType -> VkQueryType
$cmin :: VkQueryType -> VkQueryType -> VkQueryType
max :: VkQueryType -> VkQueryType -> VkQueryType
$cmax :: VkQueryType -> VkQueryType -> VkQueryType
>= :: VkQueryType -> VkQueryType -> Bool
$c>= :: VkQueryType -> VkQueryType -> Bool
> :: VkQueryType -> VkQueryType -> Bool
$c> :: VkQueryType -> VkQueryType -> Bool
<= :: VkQueryType -> VkQueryType -> Bool
$c<= :: VkQueryType -> VkQueryType -> Bool
< :: VkQueryType -> VkQueryType -> Bool
$c< :: VkQueryType -> VkQueryType -> Bool
compare :: VkQueryType -> VkQueryType -> Ordering
$ccompare :: VkQueryType -> VkQueryType -> Ordering
$cp1Ord :: Eq VkQueryType
Ord, Integer -> VkQueryType
VkQueryType -> VkQueryType
VkQueryType -> VkQueryType -> VkQueryType
(VkQueryType -> VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType)
-> (Integer -> VkQueryType)
-> Num VkQueryType
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkQueryType
$cfromInteger :: Integer -> VkQueryType
signum :: VkQueryType -> VkQueryType
$csignum :: VkQueryType -> VkQueryType
abs :: VkQueryType -> VkQueryType
$cabs :: VkQueryType -> VkQueryType
negate :: VkQueryType -> VkQueryType
$cnegate :: VkQueryType -> VkQueryType
* :: VkQueryType -> VkQueryType -> VkQueryType
$c* :: VkQueryType -> VkQueryType -> VkQueryType
- :: VkQueryType -> VkQueryType -> VkQueryType
$c- :: VkQueryType -> VkQueryType -> VkQueryType
+ :: VkQueryType -> VkQueryType -> VkQueryType
$c+ :: VkQueryType -> VkQueryType -> VkQueryType
Num, VkQueryType
VkQueryType -> VkQueryType -> Bounded VkQueryType
forall a. a -> a -> Bounded a
maxBound :: VkQueryType
$cmaxBound :: VkQueryType
minBound :: VkQueryType
$cminBound :: VkQueryType
Bounded, Ptr b -> Int -> IO VkQueryType
Ptr b -> Int -> VkQueryType -> IO ()
Ptr VkQueryType -> IO VkQueryType
Ptr VkQueryType -> Int -> IO VkQueryType
Ptr VkQueryType -> Int -> VkQueryType -> IO ()
Ptr VkQueryType -> VkQueryType -> IO ()
VkQueryType -> Int
(VkQueryType -> Int)
-> (VkQueryType -> Int)
-> (Ptr VkQueryType -> Int -> IO VkQueryType)
-> (Ptr VkQueryType -> Int -> VkQueryType -> IO ())
-> (forall b. Ptr b -> Int -> IO VkQueryType)
-> (forall b. Ptr b -> Int -> VkQueryType -> IO ())
-> (Ptr VkQueryType -> IO VkQueryType)
-> (Ptr VkQueryType -> VkQueryType -> IO ())
-> Storable VkQueryType
forall b. Ptr b -> Int -> IO VkQueryType
forall b. Ptr b -> Int -> VkQueryType -> 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 VkQueryType -> VkQueryType -> IO ()
$cpoke :: Ptr VkQueryType -> VkQueryType -> IO ()
peek :: Ptr VkQueryType -> IO VkQueryType
$cpeek :: Ptr VkQueryType -> IO VkQueryType
pokeByteOff :: Ptr b -> Int -> VkQueryType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkQueryType -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkQueryType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkQueryType
pokeElemOff :: Ptr VkQueryType -> Int -> VkQueryType -> IO ()
$cpokeElemOff :: Ptr VkQueryType -> Int -> VkQueryType -> IO ()
peekElemOff :: Ptr VkQueryType -> Int -> IO VkQueryType
$cpeekElemOff :: Ptr VkQueryType -> Int -> IO VkQueryType
alignment :: VkQueryType -> Int
$calignment :: VkQueryType -> Int
sizeOf :: VkQueryType -> Int
$csizeOf :: VkQueryType -> Int
Storable, Int -> VkQueryType
VkQueryType -> Int
VkQueryType -> [VkQueryType]
VkQueryType -> VkQueryType
VkQueryType -> VkQueryType -> [VkQueryType]
VkQueryType -> VkQueryType -> VkQueryType -> [VkQueryType]
(VkQueryType -> VkQueryType)
-> (VkQueryType -> VkQueryType)
-> (Int -> VkQueryType)
-> (VkQueryType -> Int)
-> (VkQueryType -> [VkQueryType])
-> (VkQueryType -> VkQueryType -> [VkQueryType])
-> (VkQueryType -> VkQueryType -> [VkQueryType])
-> (VkQueryType -> VkQueryType -> VkQueryType -> [VkQueryType])
-> Enum VkQueryType
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 :: VkQueryType -> VkQueryType -> VkQueryType -> [VkQueryType]
$cenumFromThenTo :: VkQueryType -> VkQueryType -> VkQueryType -> [VkQueryType]
enumFromTo :: VkQueryType -> VkQueryType -> [VkQueryType]
$cenumFromTo :: VkQueryType -> VkQueryType -> [VkQueryType]
enumFromThen :: VkQueryType -> VkQueryType -> [VkQueryType]
$cenumFromThen :: VkQueryType -> VkQueryType -> [VkQueryType]
enumFrom :: VkQueryType -> [VkQueryType]
$cenumFrom :: VkQueryType -> [VkQueryType]
fromEnum :: VkQueryType -> Int
$cfromEnum :: VkQueryType -> Int
toEnum :: Int -> VkQueryType
$ctoEnum :: Int -> VkQueryType
pred :: VkQueryType -> VkQueryType
$cpred :: VkQueryType -> VkQueryType
succ :: VkQueryType -> VkQueryType
$csucc :: VkQueryType -> VkQueryType
Enum, Typeable VkQueryType
DataType
Constr
Typeable VkQueryType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> VkQueryType -> c VkQueryType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkQueryType)
-> (VkQueryType -> Constr)
-> (VkQueryType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VkQueryType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkQueryType))
-> ((forall b. Data b => b -> b) -> VkQueryType -> VkQueryType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VkQueryType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VkQueryType -> r)
-> (forall u. (forall d. Data d => d -> u) -> VkQueryType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkQueryType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType)
-> Data VkQueryType
VkQueryType -> DataType
VkQueryType -> Constr
(forall b. Data b => b -> b) -> VkQueryType -> VkQueryType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueryType -> c VkQueryType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VkQueryType -> u
forall u. (forall d. Data d => d -> u) -> VkQueryType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueryType -> c VkQueryType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkQueryType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryType)
$cVkQueryType :: Constr
$tVkQueryType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
gmapMp :: (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
gmapM :: (forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VkQueryType -> m VkQueryType
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueryType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VkQueryType -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueryType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VkQueryType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueryType -> r
gmapT :: (forall b. Data b => b -> b) -> VkQueryType -> VkQueryType
$cgmapT :: (forall b. Data b => b -> b) -> VkQueryType -> VkQueryType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueryType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkQueryType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkQueryType)
dataTypeOf :: VkQueryType -> DataType
$cdataTypeOf :: VkQueryType -> DataType
toConstr :: VkQueryType -> Constr
$ctoConstr :: VkQueryType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueryType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueryType -> c VkQueryType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueryType -> c VkQueryType
$cp1Data :: Typeable VkQueryType
Data, (forall x. VkQueryType -> Rep VkQueryType x)
-> (forall x. Rep VkQueryType x -> VkQueryType)
-> Generic VkQueryType
forall x. Rep VkQueryType x -> VkQueryType
forall x. VkQueryType -> Rep VkQueryType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VkQueryType x -> VkQueryType
$cfrom :: forall x. VkQueryType -> Rep VkQueryType x
Generic)

instance Show VkQueryType where
        showsPrec :: Int -> VkQueryType -> ShowS
showsPrec Int
_ VkQueryType
VK_QUERY_TYPE_OCCLUSION
          = String -> ShowS
showString String
"VK_QUERY_TYPE_OCCLUSION"
        showsPrec Int
_ VkQueryType
VK_QUERY_TYPE_PIPELINE_STATISTICS
          = String -> ShowS
showString String
"VK_QUERY_TYPE_PIPELINE_STATISTICS"
        showsPrec Int
_ VkQueryType
VK_QUERY_TYPE_TIMESTAMP
          = String -> ShowS
showString String
"VK_QUERY_TYPE_TIMESTAMP"
        showsPrec Int
p (VkQueryType Int32
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"VkQueryType " 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 VkQueryType where
        readPrec :: ReadPrec VkQueryType
readPrec
          = ReadPrec VkQueryType -> ReadPrec VkQueryType
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec VkQueryType)] -> ReadPrec VkQueryType
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_QUERY_TYPE_OCCLUSION", VkQueryType -> ReadPrec VkQueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryType
VK_QUERY_TYPE_OCCLUSION),
                  (String
"VK_QUERY_TYPE_PIPELINE_STATISTICS",
                   VkQueryType -> ReadPrec VkQueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryType
VK_QUERY_TYPE_PIPELINE_STATISTICS),
                  (String
"VK_QUERY_TYPE_TIMESTAMP", VkQueryType -> ReadPrec VkQueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueryType
VK_QUERY_TYPE_TIMESTAMP)]
                 ReadPrec VkQueryType
-> ReadPrec VkQueryType -> ReadPrec VkQueryType
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int -> ReadPrec VkQueryType -> ReadPrec VkQueryType
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueryType") ReadPrec () -> ReadPrec VkQueryType -> ReadPrec VkQueryType
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Int32 -> VkQueryType
VkQueryType (Int32 -> VkQueryType) -> ReadPrec Int32 -> ReadPrec VkQueryType
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_QUERY_TYPE_OCCLUSION :: VkQueryType

pattern $bVK_QUERY_TYPE_OCCLUSION :: VkQueryType
$mVK_QUERY_TYPE_OCCLUSION :: forall r. VkQueryType -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_TYPE_OCCLUSION = VkQueryType 0

-- | Optional
pattern VK_QUERY_TYPE_PIPELINE_STATISTICS :: VkQueryType

pattern $bVK_QUERY_TYPE_PIPELINE_STATISTICS :: VkQueryType
$mVK_QUERY_TYPE_PIPELINE_STATISTICS :: forall r. VkQueryType -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_TYPE_PIPELINE_STATISTICS = VkQueryType 1

pattern VK_QUERY_TYPE_TIMESTAMP :: VkQueryType

pattern $bVK_QUERY_TYPE_TIMESTAMP :: VkQueryType
$mVK_QUERY_TYPE_TIMESTAMP :: forall r. VkQueryType -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_TYPE_TIMESTAMP = VkQueryType 2