{-# 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.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 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 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
$cp1Ord :: forall (a :: FlagType). Eq (VkQueueBitmask a)
Ord, Ptr b -> Int -> IO (VkQueueBitmask a)
Ptr b -> Int -> VkQueueBitmask a -> IO ()
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 :: Ptr b -> Int -> VkQueueBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b. Ptr b -> Int -> VkQueueBitmask a -> IO ()
peekByteOff :: 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, Typeable (VkQueueBitmask a)
DataType
Constr
Typeable (VkQueueBitmask a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueBitmask a
-> c (VkQueueBitmask a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask a))
-> (VkQueueBitmask a -> Constr)
-> (VkQueueBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueueBitmask a)))
-> ((forall b. Data b => b -> b)
-> VkQueueBitmask a -> VkQueueBitmask a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> VkQueueBitmask a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> VkQueueBitmask a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a))
-> Data (VkQueueBitmask a)
VkQueueBitmask a -> DataType
VkQueueBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkQueueBitmask a -> VkQueueBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask 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) -> VkQueueBitmask a -> u
forall u. (forall d. Data d => d -> u) -> VkQueueBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
forall (a :: FlagType). Typeable a => Typeable (VkQueueBitmask a)
forall (a :: FlagType). Typeable a => VkQueueBitmask a -> DataType
forall (a :: FlagType). Typeable a => VkQueueBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueueBitmask a -> VkQueueBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueueBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueueBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueueBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueueBitmask a))
$cVkQueueBitmask :: Constr
$tVkQueueBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkQueueBitmask a -> m (VkQueueBitmask a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkQueueBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkQueueBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueueBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkQueueBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkQueueBitmask a -> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueueBitmask a -> VkQueueBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkQueueBitmask a -> VkQueueBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueueBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkQueueBitmask a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkQueueBitmask a))
dataTypeOf :: VkQueueBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType). Typeable a => VkQueueBitmask a -> DataType
toConstr :: VkQueueBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType). Typeable a => VkQueueBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkQueueBitmask 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 (VkQueueBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkQueueBitmask a -> c (VkQueueBitmask a)
$cp1Data :: forall (a :: FlagType). Typeable a => Typeable (VkQueueBitmask a)
Data, (forall x. VkQueueBitmask a -> Rep (VkQueueBitmask a) x)
-> (forall x. Rep (VkQueueBitmask a) x -> VkQueueBitmask a)
-> Generic (VkQueueBitmask a)
forall x. Rep (VkQueueBitmask a) x -> VkQueueBitmask a
forall x. VkQueueBitmask a -> Rep (VkQueueBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkQueueBitmask a) x -> VkQueueBitmask a
forall (a :: FlagType) x.
VkQueueBitmask a -> Rep (VkQueueBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkQueueBitmask a) x -> VkQueueBitmask a
$cfrom :: forall (a :: FlagType) x.
VkQueueBitmask a -> Rep (VkQueueBitmask a) x
Generic)
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)
deriving instance Integral (VkQueueBitmask FlagMask)
deriving instance Num (VkQueueBitmask FlagMask)
deriving instance Bounded (VkQueueBitmask FlagMask)
deriving instance Enum (VkQueueBitmask FlagMask)
deriving instance Real (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 :: 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 :: 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 :: 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 :: 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
$cp1Ord :: Eq VkQueueGlobalPriorityEXT
Ord, Integer -> VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
(VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (Integer -> VkQueueGlobalPriorityEXT)
-> Num VkQueueGlobalPriorityEXT
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkQueueGlobalPriorityEXT
$cfromInteger :: Integer -> VkQueueGlobalPriorityEXT
signum :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$csignum :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
abs :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cabs :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
negate :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cnegate :: VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
* :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$c* :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
- :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$c- :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
+ :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$c+ :: VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
Num, VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT
-> VkQueueGlobalPriorityEXT -> Bounded VkQueueGlobalPriorityEXT
forall a. a -> a -> Bounded a
maxBound :: VkQueueGlobalPriorityEXT
$cmaxBound :: VkQueueGlobalPriorityEXT
minBound :: VkQueueGlobalPriorityEXT
$cminBound :: VkQueueGlobalPriorityEXT
Bounded, Ptr b -> Int -> IO VkQueueGlobalPriorityEXT
Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ()
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 :: Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkQueueGlobalPriorityEXT -> IO ()
peekByteOff :: 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, 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, Typeable VkQueueGlobalPriorityEXT
DataType
Constr
Typeable VkQueueGlobalPriorityEXT
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueGlobalPriorityEXT
-> c VkQueueGlobalPriorityEXT)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT)
-> (VkQueueGlobalPriorityEXT -> Constr)
-> (VkQueueGlobalPriorityEXT -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c VkQueueGlobalPriorityEXT))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueueGlobalPriorityEXT))
-> ((forall b. Data b => b -> b)
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT)
-> Data VkQueueGlobalPriorityEXT
VkQueueGlobalPriorityEXT -> DataType
VkQueueGlobalPriorityEXT -> Constr
(forall b. Data b => b -> b)
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueGlobalPriorityEXT
-> c VkQueueGlobalPriorityEXT
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT
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) -> VkQueueGlobalPriorityEXT -> u
forall u.
(forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueGlobalPriorityEXT
-> c VkQueueGlobalPriorityEXT
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkQueueGlobalPriorityEXT)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueueGlobalPriorityEXT)
$cVkQueueGlobalPriorityEXT :: Constr
$tVkQueueGlobalPriorityEXT :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
gmapMp :: (forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
gmapM :: (forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkQueueGlobalPriorityEXT -> m VkQueueGlobalPriorityEXT
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> u
gmapQ :: (forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> VkQueueGlobalPriorityEXT -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkQueueGlobalPriorityEXT
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
$cgmapT :: (forall b. Data b => b -> b)
-> VkQueueGlobalPriorityEXT -> VkQueueGlobalPriorityEXT
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueueGlobalPriorityEXT)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkQueueGlobalPriorityEXT)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkQueueGlobalPriorityEXT)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkQueueGlobalPriorityEXT)
dataTypeOf :: VkQueueGlobalPriorityEXT -> DataType
$cdataTypeOf :: VkQueueGlobalPriorityEXT -> DataType
toConstr :: VkQueueGlobalPriorityEXT -> Constr
$ctoConstr :: VkQueueGlobalPriorityEXT -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkQueueGlobalPriorityEXT
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueGlobalPriorityEXT
-> c VkQueueGlobalPriorityEXT
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkQueueGlobalPriorityEXT
-> c VkQueueGlobalPriorityEXT
$cp1Data :: Typeable VkQueueGlobalPriorityEXT
Data, (forall x.
VkQueueGlobalPriorityEXT -> Rep VkQueueGlobalPriorityEXT x)
-> (forall x.
Rep VkQueueGlobalPriorityEXT x -> VkQueueGlobalPriorityEXT)
-> Generic VkQueueGlobalPriorityEXT
forall x.
Rep VkQueueGlobalPriorityEXT x -> VkQueueGlobalPriorityEXT
forall x.
VkQueueGlobalPriorityEXT -> Rep VkQueueGlobalPriorityEXT x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VkQueueGlobalPriorityEXT x -> VkQueueGlobalPriorityEXT
$cfrom :: forall x.
VkQueueGlobalPriorityEXT -> Rep VkQueueGlobalPriorityEXT x
Generic)
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