{-# language CPP #-}
module Vulkan.Core10.Enums.PipelineCreateFlagBits  ( PipelineCreateFlagBits( PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT
                                                                           , PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT
                                                                           , PIPELINE_CREATE_DERIVATIVE_BIT
                                                                           , PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT
                                                                           , PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT
                                                                           , PIPELINE_CREATE_LIBRARY_BIT_KHR
                                                                           , PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV
                                                                           , PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR
                                                                           , PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR
                                                                           , PIPELINE_CREATE_DEFER_COMPILE_BIT_NV
                                                                           , PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR
                                                                           , PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR
                                                                           , PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR
                                                                           , PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR
                                                                           , PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR
                                                                           , PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR
                                                                           , PIPELINE_CREATE_DISPATCH_BASE_BIT
                                                                           , PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT
                                                                           , ..
                                                                           )
                                                   , PipelineCreateFlags
                                                   ) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
-- | VkPipelineCreateFlagBits - Bitmask controlling how a pipeline is created
--
-- = Description
--
-- -   'PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT' specifies that the
--     created pipeline will not be optimized. Using this flag /may/ reduce
--     the time taken to create the pipeline.
--
-- -   'PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT' specifies that the pipeline
--     to be created is allowed to be the parent of a pipeline that will be
--     created in a subsequent pipeline creation call.
--
-- -   'PIPELINE_CREATE_DERIVATIVE_BIT' specifies that the pipeline to be
--     created will be a child of a previously created parent pipeline.
--
-- -   'PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT' specifies that
--     any shader input variables decorated as @ViewIndex@ will be assigned
--     values as if they were decorated as @DeviceIndex@.
--
-- -   'Vulkan.Core11.Promoted_From_VK_KHR_device_group.PIPELINE_CREATE_DISPATCH_BASE'
--     specifies that a compute pipeline /can/ be used with
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.cmdDispatchBase'
--     with a non-zero base workgroup.
--
-- -   'PIPELINE_CREATE_DEFER_COMPILE_BIT_NV' specifies that a pipeline is
--     created with all shaders in the deferred state. Before using the
--     pipeline the application /must/ call
--     'Vulkan.Extensions.VK_NV_ray_tracing.compileDeferredNV' exactly once
--     on each shader in the pipeline before using the pipeline.
--
-- -   'PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR' specifies that the
--     shader compiler should capture statistics for the executables
--     produced by the compile process which /can/ later be retrieved by
--     calling
--     'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.getPipelineExecutableStatisticsKHR'.
--     Enabling this flag /must/ not affect the final compiled pipeline but
--     /may/ disable pipeline caching or otherwise affect pipeline creation
--     time.
--
-- -   'PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR' specifies
--     that the shader compiler should capture the internal representations
--     of executables produced by the compile process which /can/ later be
--     retrieved by calling
--     'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.getPipelineExecutableInternalRepresentationsKHR'.
--     Enabling this flag /must/ not affect the final compiled pipeline but
--     /may/ disable pipeline caching or otherwise affect pipeline creation
--     time.
--
-- -   'PIPELINE_CREATE_LIBRARY_BIT_KHR' specifies that the pipeline
--     /cannot/ be used directly, and instead defines a /pipeline library/
--     that /can/ be combined with other pipelines using the
--     'Vulkan.Extensions.VK_KHR_pipeline_library.PipelineLibraryCreateInfoKHR'
--     structure. This is available in raytracing pipelines.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR'
--     specifies that an any hit shader will always be present when an any
--     hit shader would be executed.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR'
--     specifies that a closest hit shader will always be present when a
--     closest hit shader would be executed.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR' specifies
--     that a miss shader will always be present when a miss shader would
--     be executed.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR'
--     specifies that an intersection shader will always be present when an
--     intersection shader would be executed.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR' specifies that
--     triangle primitives will be skipped during traversal using
--     @OpTraceKHR@.
--
-- -   'PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR' specifies that AABB
--     primitives will be skipped during traversal using @OpTraceKHR@.
--
-- -   'PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV' specifies that the
--     pipeline can be used in combination with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#device-generated-commands>.
--
-- -   'PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
--     specifies that pipeline creation will fail if a compile is required
--     for creation of a valid 'Vulkan.Core10.Handles.Pipeline' object;
--     'Vulkan.Core10.Enums.Result.PIPELINE_COMPILE_REQUIRED_EXT' will be
--     returned by pipeline creation, and the
--     'Vulkan.Core10.Handles.Pipeline' will be set to
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'.
--
-- -   When creating multiple pipelines,
--     'PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT' specifies that
--     control will be returned to the application on failure of the
--     corresponding pipeline rather than continuing to create additional
--     pipelines.
--
-- It is valid to set both 'PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT' and
-- 'PIPELINE_CREATE_DERIVATIVE_BIT'. This allows a pipeline to be both a
-- parent and possibly a child in a pipeline hierarchy. See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-pipeline-derivatives Pipeline Derivatives>
-- for more information.
--
-- = See Also
--
-- 'PipelineCreateFlags'
newtype PipelineCreateFlagBits = PipelineCreateFlagBits Flags
  deriving newtype (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
(PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> Eq PipelineCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c/= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
== :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c== :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
Eq, Eq PipelineCreateFlagBits
Eq PipelineCreateFlagBits =>
(PipelineCreateFlagBits -> PipelineCreateFlagBits -> Ordering)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits
    -> PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits
    -> PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> Ord PipelineCreateFlagBits
PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
PipelineCreateFlagBits -> PipelineCreateFlagBits -> Ordering
PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
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 :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$cmin :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
max :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$cmax :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
>= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c>= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
> :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c> :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
<= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c<= :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
< :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
$c< :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Bool
compare :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Ordering
$ccompare :: PipelineCreateFlagBits -> PipelineCreateFlagBits -> Ordering
$cp1Ord :: Eq PipelineCreateFlagBits
Ord, Ptr b -> Int -> IO PipelineCreateFlagBits
Ptr b -> Int -> PipelineCreateFlagBits -> IO ()
Ptr PipelineCreateFlagBits -> IO PipelineCreateFlagBits
Ptr PipelineCreateFlagBits -> Int -> IO PipelineCreateFlagBits
Ptr PipelineCreateFlagBits
-> Int -> PipelineCreateFlagBits -> IO ()
Ptr PipelineCreateFlagBits -> PipelineCreateFlagBits -> IO ()
PipelineCreateFlagBits -> Int
(PipelineCreateFlagBits -> Int)
-> (PipelineCreateFlagBits -> Int)
-> (Ptr PipelineCreateFlagBits -> Int -> IO PipelineCreateFlagBits)
-> (Ptr PipelineCreateFlagBits
    -> Int -> PipelineCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO PipelineCreateFlagBits)
-> (forall b. Ptr b -> Int -> PipelineCreateFlagBits -> IO ())
-> (Ptr PipelineCreateFlagBits -> IO PipelineCreateFlagBits)
-> (Ptr PipelineCreateFlagBits -> PipelineCreateFlagBits -> IO ())
-> Storable PipelineCreateFlagBits
forall b. Ptr b -> Int -> IO PipelineCreateFlagBits
forall b. Ptr b -> Int -> PipelineCreateFlagBits -> 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 PipelineCreateFlagBits -> PipelineCreateFlagBits -> IO ()
$cpoke :: Ptr PipelineCreateFlagBits -> PipelineCreateFlagBits -> IO ()
peek :: Ptr PipelineCreateFlagBits -> IO PipelineCreateFlagBits
$cpeek :: Ptr PipelineCreateFlagBits -> IO PipelineCreateFlagBits
pokeByteOff :: Ptr b -> Int -> PipelineCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PipelineCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO PipelineCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PipelineCreateFlagBits
pokeElemOff :: Ptr PipelineCreateFlagBits
-> Int -> PipelineCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr PipelineCreateFlagBits
-> Int -> PipelineCreateFlagBits -> IO ()
peekElemOff :: Ptr PipelineCreateFlagBits -> Int -> IO PipelineCreateFlagBits
$cpeekElemOff :: Ptr PipelineCreateFlagBits -> Int -> IO PipelineCreateFlagBits
alignment :: PipelineCreateFlagBits -> Int
$calignment :: PipelineCreateFlagBits -> Int
sizeOf :: PipelineCreateFlagBits -> Int
$csizeOf :: PipelineCreateFlagBits -> Int
Storable, PipelineCreateFlagBits
PipelineCreateFlagBits -> Zero PipelineCreateFlagBits
forall a. a -> Zero a
zero :: PipelineCreateFlagBits
$czero :: PipelineCreateFlagBits
Zero, Eq PipelineCreateFlagBits
PipelineCreateFlagBits
Eq PipelineCreateFlagBits =>
(PipelineCreateFlagBits
 -> PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits
    -> PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits
    -> PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> PipelineCreateFlagBits
-> (Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> Bool)
-> (PipelineCreateFlagBits -> Maybe Int)
-> (PipelineCreateFlagBits -> Int)
-> (PipelineCreateFlagBits -> Bool)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits)
-> (PipelineCreateFlagBits -> Int)
-> Bits PipelineCreateFlagBits
Int -> PipelineCreateFlagBits
PipelineCreateFlagBits -> Bool
PipelineCreateFlagBits -> Int
PipelineCreateFlagBits -> Maybe Int
PipelineCreateFlagBits -> PipelineCreateFlagBits
PipelineCreateFlagBits -> Int -> Bool
PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: PipelineCreateFlagBits -> Int
$cpopCount :: PipelineCreateFlagBits -> Int
rotateR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$crotateR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
rotateL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$crotateL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
unsafeShiftR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cunsafeShiftR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
shiftR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cshiftR :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
unsafeShiftL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cunsafeShiftL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
shiftL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cshiftL :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
isSigned :: PipelineCreateFlagBits -> Bool
$cisSigned :: PipelineCreateFlagBits -> Bool
bitSize :: PipelineCreateFlagBits -> Int
$cbitSize :: PipelineCreateFlagBits -> Int
bitSizeMaybe :: PipelineCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: PipelineCreateFlagBits -> Maybe Int
testBit :: PipelineCreateFlagBits -> Int -> Bool
$ctestBit :: PipelineCreateFlagBits -> Int -> Bool
complementBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$ccomplementBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
clearBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cclearBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
setBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$csetBit :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
bit :: Int -> PipelineCreateFlagBits
$cbit :: Int -> PipelineCreateFlagBits
zeroBits :: PipelineCreateFlagBits
$czeroBits :: PipelineCreateFlagBits
rotate :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$crotate :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
shift :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
$cshift :: PipelineCreateFlagBits -> Int -> PipelineCreateFlagBits
complement :: PipelineCreateFlagBits -> PipelineCreateFlagBits
$ccomplement :: PipelineCreateFlagBits -> PipelineCreateFlagBits
xor :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$cxor :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
.|. :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$c.|. :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
.&. :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$c.&. :: PipelineCreateFlagBits
-> PipelineCreateFlagBits -> PipelineCreateFlagBits
$cp1Bits :: Eq PipelineCreateFlagBits
Bits)

-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT"
pattern $bPIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT = PipelineCreateFlagBits 0x00000001
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT"
pattern $bPIPELINE_CREATE_ALLOW_DERIVATIVES_BIT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_ALLOW_DERIVATIVES_BIT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT = PipelineCreateFlagBits 0x00000002
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_DERIVATIVE_BIT"
pattern $bPIPELINE_CREATE_DERIVATIVE_BIT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_DERIVATIVE_BIT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_DERIVATIVE_BIT = PipelineCreateFlagBits 0x00000004
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT"
pattern $bPIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT = PipelineCreateFlagBits 0x00000200
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT"
pattern $bPIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT = PipelineCreateFlagBits 0x00000100
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_LIBRARY_BIT_KHR"
pattern $bPIPELINE_CREATE_LIBRARY_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_LIBRARY_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_LIBRARY_BIT_KHR = PipelineCreateFlagBits 0x00000800
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV"
pattern $bPIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV :: PipelineCreateFlagBits
$mPIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV = PipelineCreateFlagBits 0x00040000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR"
pattern $bPIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR = PipelineCreateFlagBits 0x00000080
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR"
pattern $bPIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR = PipelineCreateFlagBits 0x00000040
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_DEFER_COMPILE_BIT_NV"
pattern $bPIPELINE_CREATE_DEFER_COMPILE_BIT_NV :: PipelineCreateFlagBits
$mPIPELINE_CREATE_DEFER_COMPILE_BIT_NV :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_DEFER_COMPILE_BIT_NV = PipelineCreateFlagBits 0x00000020
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR = PipelineCreateFlagBits 0x00002000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR = PipelineCreateFlagBits 0x00001000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR = PipelineCreateFlagBits 0x00020000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR = PipelineCreateFlagBits 0x00010000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR = PipelineCreateFlagBits 0x00008000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR"
pattern $bPIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR :: PipelineCreateFlagBits
$mPIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR = PipelineCreateFlagBits 0x00004000
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_DISPATCH_BASE_BIT"
pattern $bPIPELINE_CREATE_DISPATCH_BASE_BIT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_DISPATCH_BASE_BIT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_DISPATCH_BASE_BIT = PipelineCreateFlagBits 0x00000010
-- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT"
pattern $bPIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT :: PipelineCreateFlagBits
$mPIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT :: forall r.
PipelineCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT = PipelineCreateFlagBits 0x00000008

type PipelineCreateFlags = PipelineCreateFlagBits

instance Show PipelineCreateFlagBits where
  showsPrec :: Int -> PipelineCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
    PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT -> String -> ShowS
showString "PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT"
    PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT -> String -> ShowS
showString "PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT"
    PIPELINE_CREATE_DERIVATIVE_BIT -> String -> ShowS
showString "PIPELINE_CREATE_DERIVATIVE_BIT"
    PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT -> String -> ShowS
showString "PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT"
    PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT -> String -> ShowS
showString "PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT"
    PIPELINE_CREATE_LIBRARY_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_LIBRARY_BIT_KHR"
    PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV -> String -> ShowS
showString "PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV"
    PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR"
    PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR"
    PIPELINE_CREATE_DEFER_COMPILE_BIT_NV -> String -> ShowS
showString "PIPELINE_CREATE_DEFER_COMPILE_BIT_NV"
    PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR"
    PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR"
    PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR"
    PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR"
    PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR"
    PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR -> String -> ShowS
showString "PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR"
    PIPELINE_CREATE_DISPATCH_BASE_BIT -> String -> ShowS
showString "PIPELINE_CREATE_DISPATCH_BASE_BIT"
    PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT -> String -> ShowS
showString "PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT"
    PipelineCreateFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PipelineCreateFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read PipelineCreateFlagBits where
  readPrec :: ReadPrec PipelineCreateFlagBits
readPrec = ReadPrec PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PipelineCreateFlagBits)]
-> ReadPrec PipelineCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT)
                            , ("PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT)
                            , ("PIPELINE_CREATE_DERIVATIVE_BIT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_DERIVATIVE_BIT)
                            , ("PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT)
                            , ("PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT)
                            , ("PIPELINE_CREATE_LIBRARY_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_LIBRARY_BIT_KHR)
                            , ("PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV)
                            , ("PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_CAPTURE_INTERNAL_REPRESENTATIONS_BIT_KHR)
                            , ("PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_CAPTURE_STATISTICS_BIT_KHR)
                            , ("PIPELINE_CREATE_DEFER_COMPILE_BIT_NV", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_DEFER_COMPILE_BIT_NV)
                            , ("PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR)
                            , ("PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR)
                            , ("PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR)
                            , ("PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR)
                            , ("PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR)
                            , ("PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR)
                            , ("PIPELINE_CREATE_DISPATCH_BASE_BIT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_DISPATCH_BASE_BIT)
                            , ("PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT", PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PipelineCreateFlagBits
PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT)]
                     ReadPrec PipelineCreateFlagBits
-> ReadPrec PipelineCreateFlagBits
-> ReadPrec PipelineCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec PipelineCreateFlagBits
-> ReadPrec PipelineCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PipelineCreateFlagBits")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       PipelineCreateFlagBits -> ReadPrec PipelineCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> PipelineCreateFlagBits
PipelineCreateFlagBits Flags
v)))