{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Queue
       (VkQueueBitmask(VkQueueBitmask, VkQueueFlags, VkQueueFlagBits,
                       VK_QUEUE_GRAPHICS_BIT, VK_QUEUE_COMPUTE_BIT, VK_QUEUE_TRANSFER_BIT,
                       VK_QUEUE_SPARSE_BINDING_BIT),
        VkQueueFlags, VkQueueFlagBits,
        VkQueueGlobalPriorityEXT(VkQueueGlobalPriorityEXT,
                                 VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT,
                                 VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT,
                                 VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT,
                                 VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT))
       where
import Data.Bits                       (Bits, FiniteBits)
import Foreign.Storable                (Storable)
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 VkQueueBitmask (a :: FlagType) = VkQueueBitmask VkFlags
                                         deriving (VkQueueBitmask a -> VkQueueBitmask a -> Bool
(VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> Eq (VkQueueBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
/= :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
== :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
Eq, Eq (VkQueueBitmask a)
Eq (VkQueueBitmask a)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Ordering)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> (VkQueueBitmask a -> VkQueueBitmask a -> Bool)
-> (VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a)
-> (VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a)
-> Ord (VkQueueBitmask a)
VkQueueBitmask a -> VkQueueBitmask a -> Bool
VkQueueBitmask a -> VkQueueBitmask a -> Ordering
VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask 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 (VkQueueBitmask a)
forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Ordering
forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a
min :: VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a
$cmin :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a
max :: VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a
$cmax :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> VkQueueBitmask a
>= :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
> :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
<= :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
< :: VkQueueBitmask a -> VkQueueBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Bool
compare :: VkQueueBitmask a -> VkQueueBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkQueueBitmask a -> VkQueueBitmask a -> Ordering
Ord, Ptr (VkQueueBitmask a) -> IO (VkQueueBitmask a)
Ptr (VkQueueBitmask a) -> Int -> IO (VkQueueBitmask a)
Ptr (VkQueueBitmask a) -> Int -> VkQueueBitmask a -> IO ()
Ptr (VkQueueBitmask a) -> VkQueueBitmask a -> IO ()
VkQueueBitmask a -> Int
(VkQueueBitmask a -> Int)
-> (VkQueueBitmask a -> Int)
-> (Ptr (VkQueueBitmask a) -> Int -> IO (VkQueueBitmask a))
-> (Ptr (VkQueueBitmask a) -> Int -> VkQueueBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkQueueBitmask a))
-> (forall b. Ptr b -> Int -> VkQueueBitmask a -> IO ())
-> (Ptr (VkQueueBitmask a) -> IO (VkQueueBitmask a))
-> (Ptr (VkQueueBitmask a) -> VkQueueBitmask a -> IO ())
-> Storable (VkQueueBitmask a)
forall b. Ptr b -> Int -> IO (VkQueueBitmask a)
forall b. Ptr b -> Int -> VkQueueBitmask 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 (VkQueueBitmask a) -> IO (VkQueueBitmask a)
forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> Int -> IO (VkQueueBitmask a)
forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> Int -> VkQueueBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> VkQueueBitmask a -> IO ()
forall (a :: FlagType). VkQueueBitmask a -> Int
forall (a :: FlagType) b. Ptr b -> Int -> IO (VkQueueBitmask a)
forall (a :: FlagType) b. Ptr b -> Int -> VkQueueBitmask a -> IO ()
poke :: Ptr (VkQueueBitmask a) -> VkQueueBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> VkQueueBitmask a -> IO ()
peek :: Ptr (VkQueueBitmask a) -> IO (VkQueueBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> IO (VkQueueBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkQueueBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b. Ptr b -> Int -> VkQueueBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkQueueBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b. Ptr b -> Int -> IO (VkQueueBitmask a)
pokeElemOff :: Ptr (VkQueueBitmask a) -> Int -> VkQueueBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> Int -> VkQueueBitmask a -> IO ()
peekElemOff :: Ptr (VkQueueBitmask a) -> Int -> IO (VkQueueBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkQueueBitmask a) -> Int -> IO (VkQueueBitmask a)
alignment :: VkQueueBitmask a -> Int
$calignment :: forall (a :: FlagType). VkQueueBitmask a -> Int
sizeOf :: VkQueueBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkQueueBitmask a -> Int
Storable)
type VkQueueFlags = VkQueueBitmask FlagMask
type VkQueueFlagBits = VkQueueBitmask FlagBit
pattern VkQueueFlagBits :: VkFlags -> VkQueueBitmask FlagBit
pattern $bVkQueueFlagBits :: VkFlags -> VkQueueBitmask FlagBit
$mVkQueueFlagBits :: forall {r}.
VkQueueBitmask FlagBit -> (VkFlags -> r) -> (Void# -> r) -> r
VkQueueFlagBits n = VkQueueBitmask n
pattern VkQueueFlags :: VkFlags -> VkQueueBitmask FlagMask
pattern $bVkQueueFlags :: VkFlags -> VkQueueBitmask FlagMask
$mVkQueueFlags :: forall {r}.
VkQueueBitmask FlagMask -> (VkFlags -> r) -> (Void# -> r) -> r
VkQueueFlags n = VkQueueBitmask n
deriving instance Bits (VkQueueBitmask FlagMask)
deriving instance FiniteBits (VkQueueBitmask FlagMask)
instance Show (VkQueueBitmask a) where
    showsPrec :: Int -> VkQueueBitmask a -> ShowS
showsPrec Int
_ VkQueueBitmask a
VK_QUEUE_GRAPHICS_BIT
      = String -> ShowS
showString String
"VK_QUEUE_GRAPHICS_BIT"
    showsPrec Int
_ VkQueueBitmask a
VK_QUEUE_COMPUTE_BIT
      = String -> ShowS
showString String
"VK_QUEUE_COMPUTE_BIT"
    showsPrec Int
_ VkQueueBitmask a
VK_QUEUE_TRANSFER_BIT
      = String -> ShowS
showString String
"VK_QUEUE_TRANSFER_BIT"
    showsPrec Int
_ VkQueueBitmask a
VK_QUEUE_SPARSE_BINDING_BIT
      = String -> ShowS
showString String
"VK_QUEUE_SPARSE_BINDING_BIT"
    showsPrec Int
p (VkQueueBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkQueueBitmask " 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 (VkQueueBitmask a) where
    readPrec :: ReadPrec (VkQueueBitmask a)
readPrec
      = ReadPrec (VkQueueBitmask a) -> ReadPrec (VkQueueBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkQueueBitmask a))]
-> ReadPrec (VkQueueBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_QUEUE_GRAPHICS_BIT", VkQueueBitmask a -> ReadPrec (VkQueueBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueBitmask a
forall (a :: FlagType). VkQueueBitmask a
VK_QUEUE_GRAPHICS_BIT),
              (String
"VK_QUEUE_COMPUTE_BIT", VkQueueBitmask a -> ReadPrec (VkQueueBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueBitmask a
forall (a :: FlagType). VkQueueBitmask a
VK_QUEUE_COMPUTE_BIT),
              (String
"VK_QUEUE_TRANSFER_BIT", VkQueueBitmask a -> ReadPrec (VkQueueBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueBitmask a
forall (a :: FlagType). VkQueueBitmask a
VK_QUEUE_TRANSFER_BIT),
              (String
"VK_QUEUE_SPARSE_BINDING_BIT", VkQueueBitmask a -> ReadPrec (VkQueueBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueBitmask a
forall (a :: FlagType). VkQueueBitmask a
VK_QUEUE_SPARSE_BINDING_BIT)]
             ReadPrec (VkQueueBitmask a)
-> ReadPrec (VkQueueBitmask a) -> ReadPrec (VkQueueBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int -> ReadPrec (VkQueueBitmask a) -> ReadPrec (VkQueueBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueueBitmask") ReadPrec ()
-> ReadPrec (VkQueueBitmask a) -> ReadPrec (VkQueueBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkQueueBitmask a
forall (a :: FlagType). VkFlags -> VkQueueBitmask a
VkQueueBitmask (VkFlags -> VkQueueBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkQueueBitmask 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)))
pattern VK_QUEUE_GRAPHICS_BIT :: VkQueueBitmask a
pattern $bVK_QUEUE_GRAPHICS_BIT :: forall (a :: FlagType). VkQueueBitmask a
$mVK_QUEUE_GRAPHICS_BIT :: forall {r} {a :: FlagType}.
VkQueueBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_GRAPHICS_BIT = VkQueueBitmask 1
pattern VK_QUEUE_COMPUTE_BIT :: VkQueueBitmask a
pattern $bVK_QUEUE_COMPUTE_BIT :: forall (a :: FlagType). VkQueueBitmask a
$mVK_QUEUE_COMPUTE_BIT :: forall {r} {a :: FlagType}.
VkQueueBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_COMPUTE_BIT = VkQueueBitmask 2
pattern VK_QUEUE_TRANSFER_BIT :: VkQueueBitmask a
pattern $bVK_QUEUE_TRANSFER_BIT :: forall (a :: FlagType). VkQueueBitmask a
$mVK_QUEUE_TRANSFER_BIT :: forall {r} {a :: FlagType}.
VkQueueBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_TRANSFER_BIT = VkQueueBitmask 4
pattern VK_QUEUE_SPARSE_BINDING_BIT :: VkQueueBitmask a
pattern $bVK_QUEUE_SPARSE_BINDING_BIT :: forall (a :: FlagType). VkQueueBitmask a
$mVK_QUEUE_SPARSE_BINDING_BIT :: forall {r} {a :: FlagType}.
VkQueueBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_SPARSE_BINDING_BIT = VkQueueBitmask 8
newtype VkQueueGlobalPriorityEXT = VkQueueGlobalPriorityEXT Int32
                                   deriving (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
(VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> Eq VkQueueGlobalPriorityEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c/= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
== :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c== :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
Eq, Eq VkQueueGlobalPriorityEXT
Eq VkQueueGlobalPriorityEXT
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> Ordering)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool)
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> Ord VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Ordering
VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
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 :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cmin :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
max :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cmax :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
>= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c>= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
> :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c> :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
<= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c<= :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
< :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
$c< :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Bool
compare :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Ordering
$ccompare :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> Ordering
Ord, Int -> VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT -> Int
VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> [VkQueueGlobalPriorityEXT]
(VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (Int -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> Int)
-> (VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT])
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT])
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT])
-> (VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT
    -> [VkQueueGlobalPriorityEXT])
-> Enum VkQueueGlobalPriorityEXT
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 :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> [VkQueueGlobalPriorityEXT]
$cenumFromThenTo :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT
-> [VkQueueGlobalPriorityEXT]
enumFromTo :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
$cenumFromTo :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
enumFromThen :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
$cenumFromThen :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
enumFrom :: VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
$cenumFrom :: VkQueueGlobalPriorityEXT -> [VkQueueGlobalPriorityEXT]
fromEnum :: VkQueueGlobalPriorityEXT -> Int
$cfromEnum :: VkQueueGlobalPriorityEXT -> Int
toEnum :: Int -> VkQueueGlobalPriorityEXT
$ctoEnum :: Int -> VkQueueGlobalPriorityEXT
pred :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cpred :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
succ :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$csucc :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
Enum, Ptr VkQueueGlobalPriorityEXT -> IO VkQueueGlobalPriorityEXT
Ptr VkQueueGlobalPriorityEXT -> Int -> IO VkQueueGlobalPriorityEXT
Ptr VkQueueGlobalPriorityEXT
-> Int -> VkQueueGlobalPriorityEXT -> IO ()
Ptr VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> IO ()
VkQueueGlobalPriorityEXT -> Int
(VkQueueGlobalPriorityEXT -> Int)
-> (VkQueueGlobalPriorityEXT -> Int)
-> (Ptr VkQueueGlobalPriorityEXT
    -> Int -> IO VkQueueGlobalPriorityEXT)
-> (Ptr VkQueueGlobalPriorityEXT
    -> Int -> VkQueueGlobalPriorityEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO VkQueueGlobalPriorityEXT)
-> (forall b. Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ())
-> (Ptr VkQueueGlobalPriorityEXT -> IO VkQueueGlobalPriorityEXT)
-> (Ptr VkQueueGlobalPriorityEXT
    -> VkQueueGlobalPriorityEXT -> IO ())
-> Storable VkQueueGlobalPriorityEXT
forall b. Ptr b -> Int -> IO VkQueueGlobalPriorityEXT
forall b. Ptr b -> Int -> VkQueueGlobalPriorityEXT -> 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 VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> IO ()
$cpoke :: Ptr VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT -> IO ()
peek :: Ptr VkQueueGlobalPriorityEXT -> IO VkQueueGlobalPriorityEXT
$cpeek :: Ptr VkQueueGlobalPriorityEXT -> IO VkQueueGlobalPriorityEXT
pokeByteOff :: forall b. Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkQueueGlobalPriorityEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkQueueGlobalPriorityEXT
pokeElemOff :: Ptr VkQueueGlobalPriorityEXT
-> Int -> VkQueueGlobalPriorityEXT -> IO ()
$cpokeElemOff :: Ptr VkQueueGlobalPriorityEXT
-> Int -> VkQueueGlobalPriorityEXT -> IO ()
peekElemOff :: Ptr VkQueueGlobalPriorityEXT -> Int -> IO VkQueueGlobalPriorityEXT
$cpeekElemOff :: Ptr VkQueueGlobalPriorityEXT -> Int -> IO VkQueueGlobalPriorityEXT
alignment :: VkQueueGlobalPriorityEXT -> Int
$calignment :: VkQueueGlobalPriorityEXT -> Int
sizeOf :: VkQueueGlobalPriorityEXT -> Int
$csizeOf :: VkQueueGlobalPriorityEXT -> Int
Storable)
instance Show VkQueueGlobalPriorityEXT where
    showsPrec :: Int -> VkQueueGlobalPriorityEXT -> ShowS
showsPrec Int
_ VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT
      = String -> ShowS
showString String
"VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT"
    showsPrec Int
_ VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT
      = String -> ShowS
showString String
"VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT"
    showsPrec Int
_ VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT
      = String -> ShowS
showString String
"VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT"
    showsPrec Int
_ VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT
      = String -> ShowS
showString String
"VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT"
    showsPrec Int
p (VkQueueGlobalPriorityEXT Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkQueueGlobalPriorityEXT " 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 VkQueueGlobalPriorityEXT where
    readPrec :: ReadPrec VkQueueGlobalPriorityEXT
readPrec
      = ReadPrec VkQueueGlobalPriorityEXT
-> ReadPrec VkQueueGlobalPriorityEXT
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkQueueGlobalPriorityEXT)]
-> ReadPrec VkQueueGlobalPriorityEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT",
               VkQueueGlobalPriorityEXT -> ReadPrec VkQueueGlobalPriorityEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT),
              (String
"VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT",
               VkQueueGlobalPriorityEXT -> ReadPrec VkQueueGlobalPriorityEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT),
              (String
"VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT",
               VkQueueGlobalPriorityEXT -> ReadPrec VkQueueGlobalPriorityEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT),
              (String
"VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT",
               VkQueueGlobalPriorityEXT -> ReadPrec VkQueueGlobalPriorityEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkQueueGlobalPriorityEXT
VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT)]
             ReadPrec VkQueueGlobalPriorityEXT
-> ReadPrec VkQueueGlobalPriorityEXT
-> ReadPrec VkQueueGlobalPriorityEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkQueueGlobalPriorityEXT
-> ReadPrec VkQueueGlobalPriorityEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkQueueGlobalPriorityEXT") ReadPrec ()
-> ReadPrec VkQueueGlobalPriorityEXT
-> ReadPrec VkQueueGlobalPriorityEXT
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT (Int32 -> VkQueueGlobalPriorityEXT)
-> ReadPrec Int32 -> ReadPrec VkQueueGlobalPriorityEXT
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_QUEUE_GLOBAL_PRIORITY_LOW_EXT ::
        VkQueueGlobalPriorityEXT
pattern $bVK_QUEUE_GLOBAL_PRIORITY_LOW_EXT :: VkQueueGlobalPriorityEXT
$mVK_QUEUE_GLOBAL_PRIORITY_LOW_EXT :: forall {r}.
VkQueueGlobalPriorityEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_GLOBAL_PRIORITY_LOW_EXT =
        VkQueueGlobalPriorityEXT 128
pattern VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT ::
        VkQueueGlobalPriorityEXT
pattern $bVK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT :: VkQueueGlobalPriorityEXT
$mVK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT :: forall {r}.
VkQueueGlobalPriorityEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_GLOBAL_PRIORITY_MEDIUM_EXT =
        VkQueueGlobalPriorityEXT 256
pattern VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT ::
        VkQueueGlobalPriorityEXT
pattern $bVK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT :: VkQueueGlobalPriorityEXT
$mVK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT :: forall {r}.
VkQueueGlobalPriorityEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_GLOBAL_PRIORITY_HIGH_EXT =
        VkQueueGlobalPriorityEXT 512
pattern VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT ::
        VkQueueGlobalPriorityEXT
pattern $bVK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT :: VkQueueGlobalPriorityEXT
$mVK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT :: forall {r}.
VkQueueGlobalPriorityEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_QUEUE_GLOBAL_PRIORITY_REALTIME_EXT =
        VkQueueGlobalPriorityEXT 1024