{-# language CPP #-}
-- No documentation found for Chapter "QueryType"
module Vulkan.Core10.Enums.QueryType  (QueryType( QUERY_TYPE_OCCLUSION
                                                , QUERY_TYPE_PIPELINE_STATISTICS
                                                , QUERY_TYPE_TIMESTAMP
                                                , QUERY_TYPE_PERFORMANCE_QUERY_INTEL
                                                , QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV
                                                , QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR
                                                , QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR
                                                , QUERY_TYPE_PERFORMANCE_QUERY_KHR
                                                , QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT
                                                , ..
                                                )) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showsPrec)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))

-- | VkQueryType - Specify the type of queries managed by a query pool
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Query.QueryPoolCreateInfo',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.cmdWriteAccelerationStructuresPropertiesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.writeAccelerationStructuresPropertiesKHR'
newtype QueryType = QueryType Int32
  deriving newtype (QueryType -> QueryType -> Bool
(QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool) -> Eq QueryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryType -> QueryType -> Bool
$c/= :: QueryType -> QueryType -> Bool
== :: QueryType -> QueryType -> Bool
$c== :: QueryType -> QueryType -> Bool
Eq, Eq QueryType
Eq QueryType
-> (QueryType -> QueryType -> Ordering)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> QueryType)
-> (QueryType -> QueryType -> QueryType)
-> Ord QueryType
QueryType -> QueryType -> Bool
QueryType -> QueryType -> Ordering
QueryType -> QueryType -> QueryType
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 :: QueryType -> QueryType -> QueryType
$cmin :: QueryType -> QueryType -> QueryType
max :: QueryType -> QueryType -> QueryType
$cmax :: QueryType -> QueryType -> QueryType
>= :: QueryType -> QueryType -> Bool
$c>= :: QueryType -> QueryType -> Bool
> :: QueryType -> QueryType -> Bool
$c> :: QueryType -> QueryType -> Bool
<= :: QueryType -> QueryType -> Bool
$c<= :: QueryType -> QueryType -> Bool
< :: QueryType -> QueryType -> Bool
$c< :: QueryType -> QueryType -> Bool
compare :: QueryType -> QueryType -> Ordering
$ccompare :: QueryType -> QueryType -> Ordering
$cp1Ord :: Eq QueryType
Ord, Ptr b -> Int -> IO QueryType
Ptr b -> Int -> QueryType -> IO ()
Ptr QueryType -> IO QueryType
Ptr QueryType -> Int -> IO QueryType
Ptr QueryType -> Int -> QueryType -> IO ()
Ptr QueryType -> QueryType -> IO ()
QueryType -> Int
(QueryType -> Int)
-> (QueryType -> Int)
-> (Ptr QueryType -> Int -> IO QueryType)
-> (Ptr QueryType -> Int -> QueryType -> IO ())
-> (forall b. Ptr b -> Int -> IO QueryType)
-> (forall b. Ptr b -> Int -> QueryType -> IO ())
-> (Ptr QueryType -> IO QueryType)
-> (Ptr QueryType -> QueryType -> IO ())
-> Storable QueryType
forall b. Ptr b -> Int -> IO QueryType
forall b. Ptr b -> Int -> QueryType -> 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 QueryType -> QueryType -> IO ()
$cpoke :: Ptr QueryType -> QueryType -> IO ()
peek :: Ptr QueryType -> IO QueryType
$cpeek :: Ptr QueryType -> IO QueryType
pokeByteOff :: Ptr b -> Int -> QueryType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueryType -> IO ()
peekByteOff :: Ptr b -> Int -> IO QueryType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueryType
pokeElemOff :: Ptr QueryType -> Int -> QueryType -> IO ()
$cpokeElemOff :: Ptr QueryType -> Int -> QueryType -> IO ()
peekElemOff :: Ptr QueryType -> Int -> IO QueryType
$cpeekElemOff :: Ptr QueryType -> Int -> IO QueryType
alignment :: QueryType -> Int
$calignment :: QueryType -> Int
sizeOf :: QueryType -> Int
$csizeOf :: QueryType -> Int
Storable, QueryType
QueryType -> Zero QueryType
forall a. a -> Zero a
zero :: QueryType
$czero :: QueryType
Zero)

-- | 'QUERY_TYPE_OCCLUSION' specifies an
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-occlusion occlusion query>.
pattern $bQUERY_TYPE_OCCLUSION :: QueryType
$mQUERY_TYPE_OCCLUSION :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_OCCLUSION                     = QueryType 0
-- | 'QUERY_TYPE_PIPELINE_STATISTICS' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-pipestats pipeline statistics query>.
pattern $bQUERY_TYPE_PIPELINE_STATISTICS :: QueryType
$mQUERY_TYPE_PIPELINE_STATISTICS :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_PIPELINE_STATISTICS           = QueryType 1
-- | 'QUERY_TYPE_TIMESTAMP' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-timestamps timestamp query>.
pattern $bQUERY_TYPE_TIMESTAMP :: QueryType
$mQUERY_TYPE_TIMESTAMP :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_TIMESTAMP                     = QueryType 2
-- | 'QUERY_TYPE_PERFORMANCE_QUERY_INTEL' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-performance-intel Intel performance query>.
pattern $bQUERY_TYPE_PERFORMANCE_QUERY_INTEL :: QueryType
$mQUERY_TYPE_PERFORMANCE_QUERY_INTEL :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_PERFORMANCE_QUERY_INTEL       = QueryType 1000210000
-- | 'QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-copying acceleration structure size query>
-- for use with
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV'.
pattern $bQUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV :: QueryType
$mQUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV = QueryType 1000165000
-- | 'QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-copying serialization acceleration structure size query>
pattern $bQUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR :: QueryType
$mQUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR = QueryType 1000150001
-- | 'QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-copying acceleration structure size query>
-- for use with
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.cmdWriteAccelerationStructuresPropertiesKHR'
-- or
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.writeAccelerationStructuresPropertiesKHR'.
pattern $bQUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR :: QueryType
$mQUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR = QueryType 1000150000
-- | 'QUERY_TYPE_PERFORMANCE_QUERY_KHR' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-performance performance query>.
pattern $bQUERY_TYPE_PERFORMANCE_QUERY_KHR :: QueryType
$mQUERY_TYPE_PERFORMANCE_QUERY_KHR :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_PERFORMANCE_QUERY_KHR         = QueryType 1000116000
-- | 'QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT' specifies a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#queries-transform-feedback transform feedback query>.
pattern $bQUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT :: QueryType
$mQUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT = QueryType 1000028004
{-# complete QUERY_TYPE_OCCLUSION,
             QUERY_TYPE_PIPELINE_STATISTICS,
             QUERY_TYPE_TIMESTAMP,
             QUERY_TYPE_PERFORMANCE_QUERY_INTEL,
             QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV,
             QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR,
             QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR,
             QUERY_TYPE_PERFORMANCE_QUERY_KHR,
             QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT :: QueryType #-}

conNameQueryType :: String
conNameQueryType :: String
conNameQueryType = String
"QueryType"

enumPrefixQueryType :: String
enumPrefixQueryType :: String
enumPrefixQueryType = String
"QUERY_TYPE_"

showTableQueryType :: [(QueryType, String)]
showTableQueryType :: [(QueryType, String)]
showTableQueryType =
  [ (QueryType
QUERY_TYPE_OCCLUSION                    , String
"OCCLUSION")
  , (QueryType
QUERY_TYPE_PIPELINE_STATISTICS          , String
"PIPELINE_STATISTICS")
  , (QueryType
QUERY_TYPE_TIMESTAMP                    , String
"TIMESTAMP")
  , (QueryType
QUERY_TYPE_PERFORMANCE_QUERY_INTEL      , String
"PERFORMANCE_QUERY_INTEL")
  , (QueryType
QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV, String
"ACCELERATION_STRUCTURE_COMPACTED_SIZE_NV")
  , (QueryType
QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR, String
"ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR")
  , (QueryType
QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR, String
"ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR")
  , (QueryType
QUERY_TYPE_PERFORMANCE_QUERY_KHR        , String
"PERFORMANCE_QUERY_KHR")
  , (QueryType
QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT, String
"TRANSFORM_FEEDBACK_STREAM_EXT")
  ]

instance Show QueryType where
  showsPrec :: Int -> QueryType -> ShowS
showsPrec =
    String
-> [(QueryType, String)]
-> String
-> (QueryType -> Int32)
-> (Int32 -> ShowS)
-> Int
-> QueryType
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixQueryType [(QueryType, String)]
showTableQueryType String
conNameQueryType (\(QueryType Int32
x) -> Int32
x) (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read QueryType where
  readPrec :: ReadPrec QueryType
readPrec = String
-> [(QueryType, String)]
-> String
-> (Int32 -> QueryType)
-> ReadPrec QueryType
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixQueryType [(QueryType, String)]
showTableQueryType String
conNameQueryType Int32 -> QueryType
QueryType