{-# language CPP #-}
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_SERIALIZATION_SIZE_KHR
                                                , QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR
                                                , QUERY_TYPE_PERFORMANCE_QUERY_KHR
                                                , QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT
                                                , ..
                                                )) where
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
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)
pattern $bQUERY_TYPE_OCCLUSION :: QueryType
$mQUERY_TYPE_OCCLUSION :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_OCCLUSION = QueryType 0
pattern $bQUERY_TYPE_PIPELINE_STATISTICS :: QueryType
$mQUERY_TYPE_PIPELINE_STATISTICS :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_PIPELINE_STATISTICS = QueryType 1
pattern $bQUERY_TYPE_TIMESTAMP :: QueryType
$mQUERY_TYPE_TIMESTAMP :: forall r. QueryType -> (Void# -> r) -> (Void# -> r) -> r
QUERY_TYPE_TIMESTAMP = QueryType 2
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
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 1000150000
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 1000165000
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
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_SERIALIZATION_SIZE_KHR,
             QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR,
             QUERY_TYPE_PERFORMANCE_QUERY_KHR,
             QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT :: QueryType #-}
instance Show QueryType where
  showsPrec :: Int -> QueryType -> ShowS
showsPrec p :: Int
p = \case
    QUERY_TYPE_OCCLUSION -> String -> ShowS
showString "QUERY_TYPE_OCCLUSION"
    QUERY_TYPE_PIPELINE_STATISTICS -> String -> ShowS
showString "QUERY_TYPE_PIPELINE_STATISTICS"
    QUERY_TYPE_TIMESTAMP -> String -> ShowS
showString "QUERY_TYPE_TIMESTAMP"
    QUERY_TYPE_PERFORMANCE_QUERY_INTEL -> String -> ShowS
showString "QUERY_TYPE_PERFORMANCE_QUERY_INTEL"
    QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR -> String -> ShowS
showString "QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR"
    QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR -> String -> ShowS
showString "QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR"
    QUERY_TYPE_PERFORMANCE_QUERY_KHR -> String -> ShowS
showString "QUERY_TYPE_PERFORMANCE_QUERY_KHR"
    QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT -> String -> ShowS
showString "QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT"
    QueryType x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "QueryType " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)
instance Read QueryType where
  readPrec :: ReadPrec QueryType
readPrec = ReadPrec QueryType -> ReadPrec QueryType
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec QueryType)] -> ReadPrec QueryType
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("QUERY_TYPE_OCCLUSION", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_OCCLUSION)
                            , ("QUERY_TYPE_PIPELINE_STATISTICS", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_PIPELINE_STATISTICS)
                            , ("QUERY_TYPE_TIMESTAMP", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_TIMESTAMP)
                            , ("QUERY_TYPE_PERFORMANCE_QUERY_INTEL", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_PERFORMANCE_QUERY_INTEL)
                            , ("QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR)
                            , ("QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR)
                            , ("QUERY_TYPE_PERFORMANCE_QUERY_KHR", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_PERFORMANCE_QUERY_KHR)
                            , ("QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT", QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryType
QUERY_TYPE_TRANSFORM_FEEDBACK_STREAM_EXT)]
                     ReadPrec QueryType -> ReadPrec QueryType -> ReadPrec QueryType
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec QueryType -> ReadPrec QueryType
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "QueryType")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       QueryType -> ReadPrec QueryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> QueryType
QueryType Int32
v)))