{-# 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.Subpass
       (VkSubpassContents(VkSubpassContents, VK_SUBPASS_CONTENTS_INLINE,
                          VK_SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS),
        VkSubpassDescriptionBitmask(VkSubpassDescriptionBitmask,
                                    VkSubpassDescriptionFlags, VkSubpassDescriptionFlagBits),
        VkSubpassDescriptionFlags, VkSubpassDescriptionFlagBits)
       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 (..))

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

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

pattern $bVK_SUBPASS_CONTENTS_INLINE :: VkSubpassContents
$mVK_SUBPASS_CONTENTS_INLINE :: forall r. VkSubpassContents -> (Void# -> r) -> (Void# -> r) -> r
VK_SUBPASS_CONTENTS_INLINE = VkSubpassContents 0

pattern VK_SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS ::
        VkSubpassContents

pattern $bVK_SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS :: VkSubpassContents
$mVK_SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS :: forall r. VkSubpassContents -> (Void# -> r) -> (Void# -> r) -> r
VK_SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS =
        VkSubpassContents 1

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

type VkSubpassDescriptionFlags =
     VkSubpassDescriptionBitmask FlagMask

type VkSubpassDescriptionFlagBits =
     VkSubpassDescriptionBitmask FlagBit

pattern VkSubpassDescriptionFlagBits ::
        VkFlags -> VkSubpassDescriptionBitmask FlagBit

pattern $bVkSubpassDescriptionFlagBits :: VkFlags -> VkSubpassDescriptionBitmask FlagBit
$mVkSubpassDescriptionFlagBits :: forall r.
VkSubpassDescriptionBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSubpassDescriptionFlagBits n =
        VkSubpassDescriptionBitmask n

pattern VkSubpassDescriptionFlags ::
        VkFlags -> VkSubpassDescriptionBitmask FlagMask

pattern $bVkSubpassDescriptionFlags :: VkFlags -> VkSubpassDescriptionBitmask FlagMask
$mVkSubpassDescriptionFlags :: forall r.
VkSubpassDescriptionBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSubpassDescriptionFlags n = VkSubpassDescriptionBitmask n

deriving instance Bits (VkSubpassDescriptionBitmask FlagMask)

deriving instance FiniteBits (VkSubpassDescriptionBitmask FlagMask)

deriving instance Integral (VkSubpassDescriptionBitmask FlagMask)

deriving instance Num (VkSubpassDescriptionBitmask FlagMask)

deriving instance Bounded (VkSubpassDescriptionBitmask FlagMask)

deriving instance Enum (VkSubpassDescriptionBitmask FlagMask)

deriving instance Real (VkSubpassDescriptionBitmask FlagMask)

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