{-# 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.Debug
       (VkDebugReportBitmaskEXT(VkDebugReportBitmaskEXT,
                                VkDebugReportFlagsEXT, VkDebugReportFlagBitsEXT,
                                VK_DEBUG_REPORT_INFORMATION_BIT_EXT,
                                VK_DEBUG_REPORT_WARNING_BIT_EXT,
                                VK_DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT,
                                VK_DEBUG_REPORT_ERROR_BIT_EXT, VK_DEBUG_REPORT_DEBUG_BIT_EXT),
        VkDebugReportFlagsEXT, VkDebugReportFlagBitsEXT,
        VkDebugReportObjectTypeEXT(VkDebugReportObjectTypeEXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT,
                                   VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT),
        VkDebugUtilsMessageSeverityBitmaskEXT(VkDebugUtilsMessageSeverityBitmaskEXT,
                                              VkDebugUtilsMessageSeverityFlagsEXT,
                                              VkDebugUtilsMessageSeverityFlagBitsEXT,
                                              VK_DEBUG_UTILS_MESSAGE_SEVERITY_VERBOSE_BIT_EXT,
                                              VK_DEBUG_UTILS_MESSAGE_SEVERITY_INFO_BIT_EXT,
                                              VK_DEBUG_UTILS_MESSAGE_SEVERITY_WARNING_BIT_EXT,
                                              VK_DEBUG_UTILS_MESSAGE_SEVERITY_ERROR_BIT_EXT),
        VkDebugUtilsMessageSeverityFlagsEXT,
        VkDebugUtilsMessageSeverityFlagBitsEXT,
        VkDebugUtilsMessageTypeBitmaskEXT(VkDebugUtilsMessageTypeBitmaskEXT,
                                          VkDebugUtilsMessageTypeFlagsEXT,
                                          VkDebugUtilsMessageTypeFlagBitsEXT,
                                          VK_DEBUG_UTILS_MESSAGE_TYPE_GENERAL_BIT_EXT,
                                          VK_DEBUG_UTILS_MESSAGE_TYPE_VALIDATION_BIT_EXT,
                                          VK_DEBUG_UTILS_MESSAGE_TYPE_PERFORMANCE_BIT_EXT),
        VkDebugUtilsMessageTypeFlagsEXT,
        VkDebugUtilsMessageTypeFlagBitsEXT)
       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 VkDebugReportBitmaskEXT (a ::
                                   FlagType) = VkDebugReportBitmaskEXT VkFlags
                                                 deriving (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
(VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> Eq (VkDebugReportBitmaskEXT a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
/= :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c/= :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
== :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c== :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
Eq, Eq (VkDebugReportBitmaskEXT a)
Eq (VkDebugReportBitmaskEXT a)
-> (VkDebugReportBitmaskEXT a
    -> VkDebugReportBitmaskEXT a -> Ordering)
-> (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> (VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool)
-> (VkDebugReportBitmaskEXT a
    -> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a)
-> (VkDebugReportBitmaskEXT a
    -> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a)
-> Ord (VkDebugReportBitmaskEXT a)
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Ordering
VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT 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 (VkDebugReportBitmaskEXT a)
forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Ordering
forall (a :: FlagType).
VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
min :: VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
$cmin :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
max :: VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
$cmax :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
>= :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c>= :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
> :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c> :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
<= :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c<= :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
< :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
$c< :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Bool
compare :: VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Ordering
$ccompare :: forall (a :: FlagType).
VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkDebugReportBitmaskEXT a)
Ord, Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a)
Ptr b -> Int -> VkDebugReportBitmaskEXT a -> IO ()
Ptr (VkDebugReportBitmaskEXT a) -> IO (VkDebugReportBitmaskEXT a)
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> IO (VkDebugReportBitmaskEXT a)
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> VkDebugReportBitmaskEXT a -> IO ()
Ptr (VkDebugReportBitmaskEXT a)
-> VkDebugReportBitmaskEXT a -> IO ()
VkDebugReportBitmaskEXT a -> Int
(VkDebugReportBitmaskEXT a -> Int)
-> (VkDebugReportBitmaskEXT a -> Int)
-> (Ptr (VkDebugReportBitmaskEXT a)
    -> Int -> IO (VkDebugReportBitmaskEXT a))
-> (Ptr (VkDebugReportBitmaskEXT a)
    -> Int -> VkDebugReportBitmaskEXT a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a))
-> (forall b. Ptr b -> Int -> VkDebugReportBitmaskEXT a -> IO ())
-> (Ptr (VkDebugReportBitmaskEXT a)
    -> IO (VkDebugReportBitmaskEXT a))
-> (Ptr (VkDebugReportBitmaskEXT a)
    -> VkDebugReportBitmaskEXT a -> IO ())
-> Storable (VkDebugReportBitmaskEXT a)
forall b. Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a)
forall b. Ptr b -> Int -> VkDebugReportBitmaskEXT 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 (VkDebugReportBitmaskEXT a) -> IO (VkDebugReportBitmaskEXT a)
forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> IO (VkDebugReportBitmaskEXT a)
forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> VkDebugReportBitmaskEXT a -> IO ()
forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> VkDebugReportBitmaskEXT a -> IO ()
forall (a :: FlagType). VkDebugReportBitmaskEXT a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkDebugReportBitmaskEXT a -> IO ()
poke :: Ptr (VkDebugReportBitmaskEXT a)
-> VkDebugReportBitmaskEXT a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> VkDebugReportBitmaskEXT a -> IO ()
peek :: Ptr (VkDebugReportBitmaskEXT a) -> IO (VkDebugReportBitmaskEXT a)
$cpeek :: forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a) -> IO (VkDebugReportBitmaskEXT a)
pokeByteOff :: Ptr b -> Int -> VkDebugReportBitmaskEXT a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkDebugReportBitmaskEXT a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkDebugReportBitmaskEXT a)
pokeElemOff :: Ptr (VkDebugReportBitmaskEXT a)
-> Int -> VkDebugReportBitmaskEXT a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> VkDebugReportBitmaskEXT a -> IO ()
peekElemOff :: Ptr (VkDebugReportBitmaskEXT a)
-> Int -> IO (VkDebugReportBitmaskEXT a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkDebugReportBitmaskEXT a)
-> Int -> IO (VkDebugReportBitmaskEXT a)
alignment :: VkDebugReportBitmaskEXT a -> Int
$calignment :: forall (a :: FlagType). VkDebugReportBitmaskEXT a -> Int
sizeOf :: VkDebugReportBitmaskEXT a -> Int
$csizeOf :: forall (a :: FlagType). VkDebugReportBitmaskEXT a -> Int
Storable, Typeable (VkDebugReportBitmaskEXT a)
DataType
Constr
Typeable (VkDebugReportBitmaskEXT a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkDebugReportBitmaskEXT a
    -> c (VkDebugReportBitmaskEXT a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkDebugReportBitmaskEXT a))
-> (VkDebugReportBitmaskEXT a -> Constr)
-> (VkDebugReportBitmaskEXT a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkDebugReportBitmaskEXT a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkDebugReportBitmaskEXT a)))
-> ((forall b. Data b => b -> b)
    -> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkDebugReportBitmaskEXT a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkDebugReportBitmaskEXT a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a))
-> Data (VkDebugReportBitmaskEXT a)
VkDebugReportBitmaskEXT a -> DataType
VkDebugReportBitmaskEXT a -> Constr
(forall b. Data b => b -> b)
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkDebugReportBitmaskEXT a
-> c (VkDebugReportBitmaskEXT a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkDebugReportBitmaskEXT 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) -> VkDebugReportBitmaskEXT a -> u
forall u.
(forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkDebugReportBitmaskEXT a)
forall (a :: FlagType).
Typeable a =>
VkDebugReportBitmaskEXT a -> DataType
forall (a :: FlagType).
Typeable a =>
VkDebugReportBitmaskEXT a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkDebugReportBitmaskEXT a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkDebugReportBitmaskEXT a
-> c (VkDebugReportBitmaskEXT a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkDebugReportBitmaskEXT a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkDebugReportBitmaskEXT a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkDebugReportBitmaskEXT a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkDebugReportBitmaskEXT a
-> c (VkDebugReportBitmaskEXT a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkDebugReportBitmaskEXT a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkDebugReportBitmaskEXT a))
$cVkDebugReportBitmaskEXT :: Constr
$tVkDebugReportBitmaskEXT :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
gmapM :: (forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkDebugReportBitmaskEXT a -> m (VkDebugReportBitmaskEXT a)
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkDebugReportBitmaskEXT a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkDebugReportBitmaskEXT a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkDebugReportBitmaskEXT a -> VkDebugReportBitmaskEXT a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkDebugReportBitmaskEXT a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkDebugReportBitmaskEXT a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkDebugReportBitmaskEXT a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkDebugReportBitmaskEXT a))
dataTypeOf :: VkDebugReportBitmaskEXT a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkDebugReportBitmaskEXT a -> DataType
toConstr :: VkDebugReportBitmaskEXT a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkDebugReportBitmaskEXT a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkDebugReportBitmaskEXT 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 (VkDebugReportBitmaskEXT a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkDebugReportBitmaskEXT a
-> c (VkDebugReportBitmaskEXT a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkDebugReportBitmaskEXT a
-> c (VkDebugReportBitmaskEXT a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkDebugReportBitmaskEXT a)
Data, (forall x.
 VkDebugReportBitmaskEXT a -> Rep (VkDebugReportBitmaskEXT a) x)
-> (forall x.
    Rep (VkDebugReportBitmaskEXT a) x -> VkDebugReportBitmaskEXT a)
-> Generic (VkDebugReportBitmaskEXT a)
forall x.
Rep (VkDebugReportBitmaskEXT a) x -> VkDebugReportBitmaskEXT a
forall x.
VkDebugReportBitmaskEXT a -> Rep (VkDebugReportBitmaskEXT a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkDebugReportBitmaskEXT a) x -> VkDebugReportBitmaskEXT a
forall (a :: FlagType) x.
VkDebugReportBitmaskEXT a -> Rep (VkDebugReportBitmaskEXT a) x
$cto :: forall (a :: FlagType) x.
Rep (VkDebugReportBitmaskEXT a) x -> VkDebugReportBitmaskEXT a
$cfrom :: forall (a :: FlagType) x.
VkDebugReportBitmaskEXT a -> Rep (VkDebugReportBitmaskEXT a) x
Generic)

type VkDebugReportFlagsEXT = VkDebugReportBitmaskEXT FlagMask

type VkDebugReportFlagBitsEXT = VkDebugReportBitmaskEXT FlagBit

pattern VkDebugReportFlagBitsEXT ::
        VkFlags -> VkDebugReportBitmaskEXT FlagBit

pattern $bVkDebugReportFlagBitsEXT :: VkFlags -> VkDebugReportBitmaskEXT FlagBit
$mVkDebugReportFlagBitsEXT :: forall r.
VkDebugReportBitmaskEXT FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugReportFlagBitsEXT n = VkDebugReportBitmaskEXT n

pattern VkDebugReportFlagsEXT ::
        VkFlags -> VkDebugReportBitmaskEXT FlagMask

pattern $bVkDebugReportFlagsEXT :: VkFlags -> VkDebugReportBitmaskEXT FlagMask
$mVkDebugReportFlagsEXT :: forall r.
VkDebugReportBitmaskEXT FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugReportFlagsEXT n = VkDebugReportBitmaskEXT n

deriving instance Bits (VkDebugReportBitmaskEXT FlagMask)

deriving instance FiniteBits (VkDebugReportBitmaskEXT FlagMask)

deriving instance Integral (VkDebugReportBitmaskEXT FlagMask)

deriving instance Num (VkDebugReportBitmaskEXT FlagMask)

deriving instance Bounded (VkDebugReportBitmaskEXT FlagMask)

deriving instance Enum (VkDebugReportBitmaskEXT FlagMask)

deriving instance Real (VkDebugReportBitmaskEXT FlagMask)

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

-- | bitpos = @0@
pattern VK_DEBUG_REPORT_INFORMATION_BIT_EXT ::
        VkDebugReportBitmaskEXT a

pattern $bVK_DEBUG_REPORT_INFORMATION_BIT_EXT :: VkDebugReportBitmaskEXT a
$mVK_DEBUG_REPORT_INFORMATION_BIT_EXT :: forall r (a :: FlagType).
VkDebugReportBitmaskEXT a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_INFORMATION_BIT_EXT =
        VkDebugReportBitmaskEXT 1

-- | bitpos = @1@
pattern VK_DEBUG_REPORT_WARNING_BIT_EXT ::
        VkDebugReportBitmaskEXT a

pattern $bVK_DEBUG_REPORT_WARNING_BIT_EXT :: VkDebugReportBitmaskEXT a
$mVK_DEBUG_REPORT_WARNING_BIT_EXT :: forall r (a :: FlagType).
VkDebugReportBitmaskEXT a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_WARNING_BIT_EXT = VkDebugReportBitmaskEXT 2

-- | bitpos = @2@
pattern VK_DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT ::
        VkDebugReportBitmaskEXT a

pattern $bVK_DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT :: VkDebugReportBitmaskEXT a
$mVK_DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT :: forall r (a :: FlagType).
VkDebugReportBitmaskEXT a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT =
        VkDebugReportBitmaskEXT 4

-- | bitpos = @3@
pattern VK_DEBUG_REPORT_ERROR_BIT_EXT :: VkDebugReportBitmaskEXT a

pattern $bVK_DEBUG_REPORT_ERROR_BIT_EXT :: VkDebugReportBitmaskEXT a
$mVK_DEBUG_REPORT_ERROR_BIT_EXT :: forall r (a :: FlagType).
VkDebugReportBitmaskEXT a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_ERROR_BIT_EXT = VkDebugReportBitmaskEXT 8

-- | bitpos = @4@
pattern VK_DEBUG_REPORT_DEBUG_BIT_EXT :: VkDebugReportBitmaskEXT a

pattern $bVK_DEBUG_REPORT_DEBUG_BIT_EXT :: VkDebugReportBitmaskEXT a
$mVK_DEBUG_REPORT_DEBUG_BIT_EXT :: forall r (a :: FlagType).
VkDebugReportBitmaskEXT a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_DEBUG_BIT_EXT = VkDebugReportBitmaskEXT 16

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

instance Show VkDebugReportObjectTypeEXT where
        showsPrec :: Int -> VkDebugReportObjectTypeEXT -> ShowS
showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT
          = String -> ShowS
showString
              String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT"
        showsPrec Int
_
          VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT
          = String -> ShowS
showString
              String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT"
        showsPrec Int
_
          VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT
          = String -> ShowS
showString
              String
"VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT"
        showsPrec Int
_ VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT
          = String -> ShowS
showString String
"VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT"
        showsPrec Int
p (VkDebugReportObjectTypeEXT Int32
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkDebugReportObjectTypeEXT " 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 VkDebugReportObjectTypeEXT where
        readPrec :: ReadPrec VkDebugReportObjectTypeEXT
readPrec
          = ReadPrec VkDebugReportObjectTypeEXT
-> ReadPrec VkDebugReportObjectTypeEXT
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec VkDebugReportObjectTypeEXT)]
-> ReadPrec VkDebugReportObjectTypeEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT),
                  (String
"VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT",
                   VkDebugReportObjectTypeEXT -> ReadPrec VkDebugReportObjectTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDebugReportObjectTypeEXT
VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT)]
                 ReadPrec VkDebugReportObjectTypeEXT
-> ReadPrec VkDebugReportObjectTypeEXT
-> ReadPrec VkDebugReportObjectTypeEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec VkDebugReportObjectTypeEXT
-> ReadPrec VkDebugReportObjectTypeEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkDebugReportObjectTypeEXT") ReadPrec ()
-> ReadPrec VkDebugReportObjectTypeEXT
-> ReadPrec VkDebugReportObjectTypeEXT
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (Int32 -> VkDebugReportObjectTypeEXT
VkDebugReportObjectTypeEXT (Int32 -> VkDebugReportObjectTypeEXT)
-> ReadPrec Int32 -> ReadPrec VkDebugReportObjectTypeEXT
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_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT =
        VkDebugReportObjectTypeEXT 0

pattern VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT =
        VkDebugReportObjectTypeEXT 1

pattern VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT =
        VkDebugReportObjectTypeEXT 2

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT =
        VkDebugReportObjectTypeEXT 3

pattern VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT =
        VkDebugReportObjectTypeEXT 4

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT =
        VkDebugReportObjectTypeEXT 5

pattern VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT =
        VkDebugReportObjectTypeEXT 6

pattern VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT =
        VkDebugReportObjectTypeEXT 7

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT =
        VkDebugReportObjectTypeEXT 8

pattern VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT =
        VkDebugReportObjectTypeEXT 9

pattern VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT =
        VkDebugReportObjectTypeEXT 10

pattern VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT =
        VkDebugReportObjectTypeEXT 11

pattern VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT =
        VkDebugReportObjectTypeEXT 12

pattern VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT =
        VkDebugReportObjectTypeEXT 13

pattern VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT =
        VkDebugReportObjectTypeEXT 14

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT =
        VkDebugReportObjectTypeEXT 15

pattern VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT =
        VkDebugReportObjectTypeEXT 16

pattern VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT =
        VkDebugReportObjectTypeEXT 17

pattern VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT =
        VkDebugReportObjectTypeEXT 18

pattern VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT =
        VkDebugReportObjectTypeEXT 19

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT =
        VkDebugReportObjectTypeEXT 20

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT =
        VkDebugReportObjectTypeEXT 21

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT =
        VkDebugReportObjectTypeEXT 22

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT =
        VkDebugReportObjectTypeEXT 23

pattern VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT =
        VkDebugReportObjectTypeEXT 24

pattern VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT =
        VkDebugReportObjectTypeEXT 25

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT =
        VkDebugReportObjectTypeEXT 26

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT =
        VkDebugReportObjectTypeEXT 27

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT
        :: VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT =
        VkDebugReportObjectTypeEXT 28

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT =
        VkDebugReportObjectTypeEXT 29

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT =
        VkDebugReportObjectTypeEXT 30

pattern VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_OBJECT_TABLE_NVX_EXT =
        VkDebugReportObjectTypeEXT 31

pattern VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT
        :: VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NVX_EXT
        = VkDebugReportObjectTypeEXT 32

pattern VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT :: forall r.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT =
        VkDebugReportObjectTypeEXT 33

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

type VkDebugUtilsMessageSeverityFlagsEXT =
     VkDebugUtilsMessageSeverityBitmaskEXT FlagMask

type VkDebugUtilsMessageSeverityFlagBitsEXT =
     VkDebugUtilsMessageSeverityBitmaskEXT FlagBit

pattern VkDebugUtilsMessageSeverityFlagBitsEXT ::
        VkFlags -> VkDebugUtilsMessageSeverityBitmaskEXT FlagBit

pattern $bVkDebugUtilsMessageSeverityFlagBitsEXT :: VkFlags -> VkDebugUtilsMessageSeverityBitmaskEXT FlagBit
$mVkDebugUtilsMessageSeverityFlagBitsEXT :: forall r.
VkDebugUtilsMessageSeverityBitmaskEXT FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugUtilsMessageSeverityFlagBitsEXT n =
        VkDebugUtilsMessageSeverityBitmaskEXT n

pattern VkDebugUtilsMessageSeverityFlagsEXT ::
        VkFlags -> VkDebugUtilsMessageSeverityBitmaskEXT FlagMask

pattern $bVkDebugUtilsMessageSeverityFlagsEXT :: VkFlags -> VkDebugUtilsMessageSeverityBitmaskEXT FlagMask
$mVkDebugUtilsMessageSeverityFlagsEXT :: forall r.
VkDebugUtilsMessageSeverityBitmaskEXT FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugUtilsMessageSeverityFlagsEXT n =
        VkDebugUtilsMessageSeverityBitmaskEXT n

deriving instance
         Bits (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         FiniteBits (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         Integral (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         Num (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         Bounded (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         Enum (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

deriving instance
         Real (VkDebugUtilsMessageSeverityBitmaskEXT FlagMask)

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

-- | bitpos = @0@
pattern VK_DEBUG_UTILS_MESSAGE_SEVERITY_VERBOSE_BIT_EXT ::
        VkDebugUtilsMessageSeverityBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_SEVERITY_VERBOSE_BIT_EXT :: VkDebugUtilsMessageSeverityBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_SEVERITY_VERBOSE_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageSeverityBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_SEVERITY_VERBOSE_BIT_EXT =
        VkDebugUtilsMessageSeverityBitmaskEXT 1

-- | bitpos = @4@
pattern VK_DEBUG_UTILS_MESSAGE_SEVERITY_INFO_BIT_EXT ::
        VkDebugUtilsMessageSeverityBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_SEVERITY_INFO_BIT_EXT :: VkDebugUtilsMessageSeverityBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_SEVERITY_INFO_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageSeverityBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_SEVERITY_INFO_BIT_EXT =
        VkDebugUtilsMessageSeverityBitmaskEXT 16

-- | bitpos = @8@
pattern VK_DEBUG_UTILS_MESSAGE_SEVERITY_WARNING_BIT_EXT ::
        VkDebugUtilsMessageSeverityBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_SEVERITY_WARNING_BIT_EXT :: VkDebugUtilsMessageSeverityBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_SEVERITY_WARNING_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageSeverityBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_SEVERITY_WARNING_BIT_EXT =
        VkDebugUtilsMessageSeverityBitmaskEXT 256

-- | bitpos = @12@
pattern VK_DEBUG_UTILS_MESSAGE_SEVERITY_ERROR_BIT_EXT ::
        VkDebugUtilsMessageSeverityBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_SEVERITY_ERROR_BIT_EXT :: VkDebugUtilsMessageSeverityBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_SEVERITY_ERROR_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageSeverityBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_SEVERITY_ERROR_BIT_EXT =
        VkDebugUtilsMessageSeverityBitmaskEXT 4096

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

type VkDebugUtilsMessageTypeFlagsEXT =
     VkDebugUtilsMessageTypeBitmaskEXT FlagMask

type VkDebugUtilsMessageTypeFlagBitsEXT =
     VkDebugUtilsMessageTypeBitmaskEXT FlagBit

pattern VkDebugUtilsMessageTypeFlagBitsEXT ::
        VkFlags -> VkDebugUtilsMessageTypeBitmaskEXT FlagBit

pattern $bVkDebugUtilsMessageTypeFlagBitsEXT :: VkFlags -> VkDebugUtilsMessageTypeBitmaskEXT FlagBit
$mVkDebugUtilsMessageTypeFlagBitsEXT :: forall r.
VkDebugUtilsMessageTypeBitmaskEXT FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugUtilsMessageTypeFlagBitsEXT n =
        VkDebugUtilsMessageTypeBitmaskEXT n

pattern VkDebugUtilsMessageTypeFlagsEXT ::
        VkFlags -> VkDebugUtilsMessageTypeBitmaskEXT FlagMask

pattern $bVkDebugUtilsMessageTypeFlagsEXT :: VkFlags -> VkDebugUtilsMessageTypeBitmaskEXT FlagMask
$mVkDebugUtilsMessageTypeFlagsEXT :: forall r.
VkDebugUtilsMessageTypeBitmaskEXT FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkDebugUtilsMessageTypeFlagsEXT n =
        VkDebugUtilsMessageTypeBitmaskEXT n

deriving instance Bits (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance
         FiniteBits (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance
         Integral (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance Num (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance
         Bounded (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance Enum (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

deriving instance Real (VkDebugUtilsMessageTypeBitmaskEXT FlagMask)

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

-- | bitpos = @0@
pattern VK_DEBUG_UTILS_MESSAGE_TYPE_GENERAL_BIT_EXT ::
        VkDebugUtilsMessageTypeBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_TYPE_GENERAL_BIT_EXT :: VkDebugUtilsMessageTypeBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_TYPE_GENERAL_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageTypeBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_TYPE_GENERAL_BIT_EXT =
        VkDebugUtilsMessageTypeBitmaskEXT 1

-- | bitpos = @1@
pattern VK_DEBUG_UTILS_MESSAGE_TYPE_VALIDATION_BIT_EXT ::
        VkDebugUtilsMessageTypeBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_TYPE_VALIDATION_BIT_EXT :: VkDebugUtilsMessageTypeBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_TYPE_VALIDATION_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageTypeBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_TYPE_VALIDATION_BIT_EXT =
        VkDebugUtilsMessageTypeBitmaskEXT 2

-- | bitpos = @2@
pattern VK_DEBUG_UTILS_MESSAGE_TYPE_PERFORMANCE_BIT_EXT ::
        VkDebugUtilsMessageTypeBitmaskEXT a

pattern $bVK_DEBUG_UTILS_MESSAGE_TYPE_PERFORMANCE_BIT_EXT :: VkDebugUtilsMessageTypeBitmaskEXT a
$mVK_DEBUG_UTILS_MESSAGE_TYPE_PERFORMANCE_BIT_EXT :: forall r (a :: FlagType).
VkDebugUtilsMessageTypeBitmaskEXT a
-> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_UTILS_MESSAGE_TYPE_PERFORMANCE_BIT_EXT =
        VkDebugUtilsMessageTypeBitmaskEXT 4