{-# language CPP #-}
module Vulkan.Core10.Enums.DynamicState  (DynamicState( DYNAMIC_STATE_VIEWPORT
                                                      , DYNAMIC_STATE_SCISSOR
                                                      , DYNAMIC_STATE_LINE_WIDTH
                                                      , DYNAMIC_STATE_DEPTH_BIAS
                                                      , DYNAMIC_STATE_BLEND_CONSTANTS
                                                      , DYNAMIC_STATE_DEPTH_BOUNDS
                                                      , DYNAMIC_STATE_STENCIL_COMPARE_MASK
                                                      , DYNAMIC_STATE_STENCIL_WRITE_MASK
                                                      , DYNAMIC_STATE_STENCIL_REFERENCE
                                                      , DYNAMIC_STATE_STENCIL_OP_EXT
                                                      , DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT
                                                      , DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT
                                                      , DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT
                                                      , DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT
                                                      , DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT
                                                      , DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT
                                                      , DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT
                                                      , DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT
                                                      , DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT
                                                      , DYNAMIC_STATE_FRONT_FACE_EXT
                                                      , DYNAMIC_STATE_CULL_MODE_EXT
                                                      , DYNAMIC_STATE_LINE_STIPPLE_EXT
                                                      , DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV
                                                      , DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV
                                                      , DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV
                                                      , DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT
                                                      , DYNAMIC_STATE_DISCARD_RECTANGLE_EXT
                                                      , DYNAMIC_STATE_VIEWPORT_W_SCALING_NV
                                                      , ..
                                                      )) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
-- | VkDynamicState - Indicate which dynamic state is taken from dynamic
-- state commands
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'
newtype DynamicState = DynamicState Int32
  deriving newtype (DynamicState -> DynamicState -> Bool
(DynamicState -> DynamicState -> Bool)
-> (DynamicState -> DynamicState -> Bool) -> Eq DynamicState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DynamicState -> DynamicState -> Bool
$c/= :: DynamicState -> DynamicState -> Bool
== :: DynamicState -> DynamicState -> Bool
$c== :: DynamicState -> DynamicState -> Bool
Eq, Eq DynamicState
Eq DynamicState =>
(DynamicState -> DynamicState -> Ordering)
-> (DynamicState -> DynamicState -> Bool)
-> (DynamicState -> DynamicState -> Bool)
-> (DynamicState -> DynamicState -> Bool)
-> (DynamicState -> DynamicState -> Bool)
-> (DynamicState -> DynamicState -> DynamicState)
-> (DynamicState -> DynamicState -> DynamicState)
-> Ord DynamicState
DynamicState -> DynamicState -> Bool
DynamicState -> DynamicState -> Ordering
DynamicState -> DynamicState -> DynamicState
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 :: DynamicState -> DynamicState -> DynamicState
$cmin :: DynamicState -> DynamicState -> DynamicState
max :: DynamicState -> DynamicState -> DynamicState
$cmax :: DynamicState -> DynamicState -> DynamicState
>= :: DynamicState -> DynamicState -> Bool
$c>= :: DynamicState -> DynamicState -> Bool
> :: DynamicState -> DynamicState -> Bool
$c> :: DynamicState -> DynamicState -> Bool
<= :: DynamicState -> DynamicState -> Bool
$c<= :: DynamicState -> DynamicState -> Bool
< :: DynamicState -> DynamicState -> Bool
$c< :: DynamicState -> DynamicState -> Bool
compare :: DynamicState -> DynamicState -> Ordering
$ccompare :: DynamicState -> DynamicState -> Ordering
$cp1Ord :: Eq DynamicState
Ord, Ptr b -> Int -> IO DynamicState
Ptr b -> Int -> DynamicState -> IO ()
Ptr DynamicState -> IO DynamicState
Ptr DynamicState -> Int -> IO DynamicState
Ptr DynamicState -> Int -> DynamicState -> IO ()
Ptr DynamicState -> DynamicState -> IO ()
DynamicState -> Int
(DynamicState -> Int)
-> (DynamicState -> Int)
-> (Ptr DynamicState -> Int -> IO DynamicState)
-> (Ptr DynamicState -> Int -> DynamicState -> IO ())
-> (forall b. Ptr b -> Int -> IO DynamicState)
-> (forall b. Ptr b -> Int -> DynamicState -> IO ())
-> (Ptr DynamicState -> IO DynamicState)
-> (Ptr DynamicState -> DynamicState -> IO ())
-> Storable DynamicState
forall b. Ptr b -> Int -> IO DynamicState
forall b. Ptr b -> Int -> DynamicState -> 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 DynamicState -> DynamicState -> IO ()
$cpoke :: Ptr DynamicState -> DynamicState -> IO ()
peek :: Ptr DynamicState -> IO DynamicState
$cpeek :: Ptr DynamicState -> IO DynamicState
pokeByteOff :: Ptr b -> Int -> DynamicState -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DynamicState -> IO ()
peekByteOff :: Ptr b -> Int -> IO DynamicState
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DynamicState
pokeElemOff :: Ptr DynamicState -> Int -> DynamicState -> IO ()
$cpokeElemOff :: Ptr DynamicState -> Int -> DynamicState -> IO ()
peekElemOff :: Ptr DynamicState -> Int -> IO DynamicState
$cpeekElemOff :: Ptr DynamicState -> Int -> IO DynamicState
alignment :: DynamicState -> Int
$calignment :: DynamicState -> Int
sizeOf :: DynamicState -> Int
$csizeOf :: DynamicState -> Int
Storable, DynamicState
DynamicState -> Zero DynamicState
forall a. a -> Zero a
zero :: DynamicState
$czero :: DynamicState
Zero)

-- | 'DYNAMIC_STATE_VIEWPORT' specifies that the @pViewports@ state in
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' will be ignored
-- and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetViewport' before any draw
-- commands. The number of viewports used by a pipeline is still specified
-- by the @viewportCount@ member of
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'.
pattern $bDYNAMIC_STATE_VIEWPORT :: DynamicState
$mDYNAMIC_STATE_VIEWPORT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VIEWPORT = DynamicState 0
-- | 'DYNAMIC_STATE_SCISSOR' specifies that the @pScissors@ state in
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' will be ignored
-- and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetScissor' before any draw
-- commands. The number of scissor rectangles used by a pipeline is still
-- specified by the @scissorCount@ member of
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'.
pattern $bDYNAMIC_STATE_SCISSOR :: DynamicState
$mDYNAMIC_STATE_SCISSOR :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_SCISSOR = DynamicState 1
-- | 'DYNAMIC_STATE_LINE_WIDTH' specifies that the @lineWidth@ state in
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetLineWidth' before any draw
-- commands that generate line primitives for the rasterizer.
pattern $bDYNAMIC_STATE_LINE_WIDTH :: DynamicState
$mDYNAMIC_STATE_LINE_WIDTH :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_LINE_WIDTH = DynamicState 2
-- | 'DYNAMIC_STATE_DEPTH_BIAS' specifies that the @depthBiasConstantFactor@,
-- @depthBiasClamp@ and @depthBiasSlopeFactor@ states in
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetDepthBias' before any draws
-- are performed with @depthBiasEnable@ in
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' set to
-- 'Vulkan.Core10.FundamentalTypes.TRUE'.
pattern $bDYNAMIC_STATE_DEPTH_BIAS :: DynamicState
$mDYNAMIC_STATE_DEPTH_BIAS :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_BIAS = DynamicState 3
-- | 'DYNAMIC_STATE_BLEND_CONSTANTS' specifies that the @blendConstants@
-- state in 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo' will
-- be ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetBlendConstants' before any
-- draws are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState' member
-- @blendEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE' and any of
-- the blend functions using a constant blend color.
pattern $bDYNAMIC_STATE_BLEND_CONSTANTS :: DynamicState
$mDYNAMIC_STATE_BLEND_CONSTANTS :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_BLEND_CONSTANTS = DynamicState 4
-- | 'DYNAMIC_STATE_DEPTH_BOUNDS' specifies that the @minDepthBounds@ and
-- @maxDepthBounds@ states of
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetDepthBounds' before any draws
-- are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' member
-- @depthBoundsTestEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE'.
pattern $bDYNAMIC_STATE_DEPTH_BOUNDS :: DynamicState
$mDYNAMIC_STATE_DEPTH_BOUNDS :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_BOUNDS = DynamicState 5
-- | 'DYNAMIC_STATE_STENCIL_COMPARE_MASK' specifies that the @compareMask@
-- state in 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'
-- for both @front@ and @back@ will be ignored and /must/ be set
-- dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilCompareMask' before
-- any draws are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' member
-- @stencilTestEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE'
pattern $bDYNAMIC_STATE_STENCIL_COMPARE_MASK :: DynamicState
$mDYNAMIC_STATE_STENCIL_COMPARE_MASK :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_STENCIL_COMPARE_MASK = DynamicState 6
-- | 'DYNAMIC_STATE_STENCIL_WRITE_MASK' specifies that the @writeMask@ state
-- in 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' for both
-- @front@ and @back@ will be ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilWriteMask' before any
-- draws are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' member
-- @stencilTestEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE'
pattern $bDYNAMIC_STATE_STENCIL_WRITE_MASK :: DynamicState
$mDYNAMIC_STATE_STENCIL_WRITE_MASK :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_STENCIL_WRITE_MASK = DynamicState 7
-- | 'DYNAMIC_STATE_STENCIL_REFERENCE' specifies that the @reference@ state
-- in 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' for both
-- @front@ and @back@ will be ignored and /must/ be set dynamically with
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilReference' before any
-- draws are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' member
-- @stencilTestEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE'
pattern $bDYNAMIC_STATE_STENCIL_REFERENCE :: DynamicState
$mDYNAMIC_STATE_STENCIL_REFERENCE :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_STENCIL_REFERENCE = DynamicState 8
-- | 'DYNAMIC_STATE_STENCIL_OP_EXT' specifies that the @failOp@, @passOp@,
-- @depthFailOp@, and @compareOp@ states in
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' for both
-- @front@ and @back@ will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetStencilOpEXT'
-- before any draws are performed with a pipeline state with
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' member
-- @stencilTestEnable@ set to 'Vulkan.Core10.FundamentalTypes.TRUE'
pattern $bDYNAMIC_STATE_STENCIL_OP_EXT :: DynamicState
$mDYNAMIC_STATE_STENCIL_OP_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_STENCIL_OP_EXT = DynamicState 1000267011
-- | 'DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT' specifies that the
-- @stencilTestEnable@ state in
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetStencilTestEnableEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT :: DynamicState
$mDYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT = DynamicState 1000267010
-- | 'DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT' specifies that the
-- @depthBoundsTestEnable@ state in
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnableEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT :: DynamicState
$mDYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT = DynamicState 1000267009
-- | 'DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT' specifies that the @depthCompareOp@
-- state in 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthCompareOpEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_DEPTH_COMPARE_OP_EXT :: DynamicState
$mDYNAMIC_STATE_DEPTH_COMPARE_OP_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT = DynamicState 1000267008
-- | 'DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT' specifies that the
-- @depthWriteEnable@ state in
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnableEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT :: DynamicState
$mDYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT = DynamicState 1000267007
-- | 'DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT' specifies that the
-- @depthTestEnable@ state in
-- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthTestEnableEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT :: DynamicState
$mDYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT = DynamicState 1000267006
-- | 'DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT' specifies that the
-- @stride@ state in 'Vulkan.Core10.Pipeline.VertexInputBindingDescription'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT :: DynamicState
$mDYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT = DynamicState 1000267005
-- | 'DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' specifies that the @scissorCount@
-- and @pScissors@ state in
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' will be ignored
-- and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT :: DynamicState
$mDYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT = DynamicState 1000267004
-- | 'DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' specifies that the
-- @viewportCount@ and @pViewports@ state in
-- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo' will be ignored
-- and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
-- before any draw call.
pattern $bDYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT :: DynamicState
$mDYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT = DynamicState 1000267003
-- | 'DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT' specifies that the @topology@
-- state in 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'
-- only specifies the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class>,
-- and the specific topology order and adjacency /must/ be set dynamically
-- with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT'
-- before any draw commands.
pattern $bDYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT :: DynamicState
$mDYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT = DynamicState 1000267002
-- | 'DYNAMIC_STATE_FRONT_FACE_EXT' specifies that the @frontFace@ state in
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetFrontFaceEXT'
-- before any draw commands.
pattern $bDYNAMIC_STATE_FRONT_FACE_EXT :: DynamicState
$mDYNAMIC_STATE_FRONT_FACE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_FRONT_FACE_EXT = DynamicState 1000267001
-- | 'DYNAMIC_STATE_CULL_MODE_EXT' specifies that the @cullMode@ state in
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo' will be
-- ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetCullModeEXT'
-- before any draw commands.
pattern $bDYNAMIC_STATE_CULL_MODE_EXT :: DynamicState
$mDYNAMIC_STATE_CULL_MODE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_CULL_MODE_EXT = DynamicState 1000267000
-- | 'DYNAMIC_STATE_LINE_STIPPLE_EXT' specifies that the @lineStippleFactor@
-- and @lineStipplePattern@ state in
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT'
-- before any draws are performed with a pipeline state with
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'
-- member @stippledLineEnable@ set to
-- 'Vulkan.Core10.FundamentalTypes.TRUE'.
pattern $bDYNAMIC_STATE_LINE_STIPPLE_EXT :: DynamicState
$mDYNAMIC_STATE_LINE_STIPPLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_LINE_STIPPLE_EXT = DynamicState 1000259000
-- | 'DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV' specifies that the
-- @pExclusiveScissors@ state in
-- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV'
-- before any draw commands. The number of exclusive scissor rectangles
-- used by a pipeline is still specified by the @exclusiveScissorCount@
-- member of
-- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'.
pattern $bDYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV :: DynamicState
$mDYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV = DynamicState 1000205001
-- | 'DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV' specifies that the
-- coarse sample order state in
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportCoarseSampleOrderStateCreateInfoNV'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV'
-- before any draw commands.
pattern $bDYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV :: DynamicState
$mDYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV = DynamicState 1000164006
-- | 'DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' specifies that the
-- @pShadingRatePalettes@ state in
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV'
-- before any draw commands.
pattern $bDYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV :: DynamicState
$mDYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV = DynamicState 1000164004
-- | 'DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' specifies that the
-- @sampleLocationsInfo@ state in
-- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT'
-- before any draw or clear commands. Enabling custom sample locations is
-- still indicated by the @sampleLocationsEnable@ member of
-- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'.
pattern $bDYNAMIC_STATE_SAMPLE_LOCATIONS_EXT :: DynamicState
$mDYNAMIC_STATE_SAMPLE_LOCATIONS_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT = DynamicState 1000143000
-- | 'DYNAMIC_STATE_DISCARD_RECTANGLE_EXT' specifies that the
-- @pDiscardRectangles@ state in
-- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT'
-- before any draw or clear commands. The
-- 'Vulkan.Extensions.VK_EXT_discard_rectangles.DiscardRectangleModeEXT'
-- and the number of active discard rectangles is still specified by the
-- @discardRectangleMode@ and @discardRectangleCount@ members of
-- 'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'.
pattern $bDYNAMIC_STATE_DISCARD_RECTANGLE_EXT :: DynamicState
$mDYNAMIC_STATE_DISCARD_RECTANGLE_EXT :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_DISCARD_RECTANGLE_EXT = DynamicState 1000099000
-- | 'DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' specifies that the
-- @pViewportScalings@ state in
-- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
-- will be ignored and /must/ be set dynamically with
-- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV'
-- before any draws are performed with a pipeline state with
-- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
-- member @viewportScalingEnable@ set to
-- 'Vulkan.Core10.FundamentalTypes.TRUE'
pattern $bDYNAMIC_STATE_VIEWPORT_W_SCALING_NV :: DynamicState
$mDYNAMIC_STATE_VIEWPORT_W_SCALING_NV :: forall r. DynamicState -> (Void# -> r) -> (Void# -> r) -> r
DYNAMIC_STATE_VIEWPORT_W_SCALING_NV = DynamicState 1000087000
{-# complete DYNAMIC_STATE_VIEWPORT,
             DYNAMIC_STATE_SCISSOR,
             DYNAMIC_STATE_LINE_WIDTH,
             DYNAMIC_STATE_DEPTH_BIAS,
             DYNAMIC_STATE_BLEND_CONSTANTS,
             DYNAMIC_STATE_DEPTH_BOUNDS,
             DYNAMIC_STATE_STENCIL_COMPARE_MASK,
             DYNAMIC_STATE_STENCIL_WRITE_MASK,
             DYNAMIC_STATE_STENCIL_REFERENCE,
             DYNAMIC_STATE_STENCIL_OP_EXT,
             DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT,
             DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT,
             DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT,
             DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT,
             DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT,
             DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT,
             DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT,
             DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT,
             DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT,
             DYNAMIC_STATE_FRONT_FACE_EXT,
             DYNAMIC_STATE_CULL_MODE_EXT,
             DYNAMIC_STATE_LINE_STIPPLE_EXT,
             DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV,
             DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV,
             DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV,
             DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT,
             DYNAMIC_STATE_DISCARD_RECTANGLE_EXT,
             DYNAMIC_STATE_VIEWPORT_W_SCALING_NV :: DynamicState #-}

instance Show DynamicState where
  showsPrec :: Int -> DynamicState -> ShowS
showsPrec p :: Int
p = \case
    DYNAMIC_STATE_VIEWPORT -> String -> ShowS
showString "DYNAMIC_STATE_VIEWPORT"
    DYNAMIC_STATE_SCISSOR -> String -> ShowS
showString "DYNAMIC_STATE_SCISSOR"
    DYNAMIC_STATE_LINE_WIDTH -> String -> ShowS
showString "DYNAMIC_STATE_LINE_WIDTH"
    DYNAMIC_STATE_DEPTH_BIAS -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_BIAS"
    DYNAMIC_STATE_BLEND_CONSTANTS -> String -> ShowS
showString "DYNAMIC_STATE_BLEND_CONSTANTS"
    DYNAMIC_STATE_DEPTH_BOUNDS -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_BOUNDS"
    DYNAMIC_STATE_STENCIL_COMPARE_MASK -> String -> ShowS
showString "DYNAMIC_STATE_STENCIL_COMPARE_MASK"
    DYNAMIC_STATE_STENCIL_WRITE_MASK -> String -> ShowS
showString "DYNAMIC_STATE_STENCIL_WRITE_MASK"
    DYNAMIC_STATE_STENCIL_REFERENCE -> String -> ShowS
showString "DYNAMIC_STATE_STENCIL_REFERENCE"
    DYNAMIC_STATE_STENCIL_OP_EXT -> String -> ShowS
showString "DYNAMIC_STATE_STENCIL_OP_EXT"
    DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT"
    DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT"
    DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT"
    DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT"
    DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT"
    DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT"
    DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT -> String -> ShowS
showString "DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT"
    DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT -> String -> ShowS
showString "DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT"
    DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT -> String -> ShowS
showString "DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT"
    DYNAMIC_STATE_FRONT_FACE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_FRONT_FACE_EXT"
    DYNAMIC_STATE_CULL_MODE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_CULL_MODE_EXT"
    DYNAMIC_STATE_LINE_STIPPLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_LINE_STIPPLE_EXT"
    DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV -> String -> ShowS
showString "DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV"
    DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV -> String -> ShowS
showString "DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV"
    DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV -> String -> ShowS
showString "DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV"
    DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT -> String -> ShowS
showString "DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT"
    DYNAMIC_STATE_DISCARD_RECTANGLE_EXT -> String -> ShowS
showString "DYNAMIC_STATE_DISCARD_RECTANGLE_EXT"
    DYNAMIC_STATE_VIEWPORT_W_SCALING_NV -> String -> ShowS
showString "DYNAMIC_STATE_VIEWPORT_W_SCALING_NV"
    DynamicState x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DynamicState " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read DynamicState where
  readPrec :: ReadPrec DynamicState
readPrec = ReadPrec DynamicState -> ReadPrec DynamicState
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DynamicState)] -> ReadPrec DynamicState
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DYNAMIC_STATE_VIEWPORT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VIEWPORT)
                            , ("DYNAMIC_STATE_SCISSOR", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_SCISSOR)
                            , ("DYNAMIC_STATE_LINE_WIDTH", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_LINE_WIDTH)
                            , ("DYNAMIC_STATE_DEPTH_BIAS", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_BIAS)
                            , ("DYNAMIC_STATE_BLEND_CONSTANTS", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_BLEND_CONSTANTS)
                            , ("DYNAMIC_STATE_DEPTH_BOUNDS", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_BOUNDS)
                            , ("DYNAMIC_STATE_STENCIL_COMPARE_MASK", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_STENCIL_COMPARE_MASK)
                            , ("DYNAMIC_STATE_STENCIL_WRITE_MASK", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_STENCIL_WRITE_MASK)
                            , ("DYNAMIC_STATE_STENCIL_REFERENCE", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_STENCIL_REFERENCE)
                            , ("DYNAMIC_STATE_STENCIL_OP_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_STENCIL_OP_EXT)
                            , ("DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT)
                            , ("DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT)
                            , ("DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT)
                            , ("DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT)
                            , ("DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT)
                            , ("DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT)
                            , ("DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT)
                            , ("DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT)
                            , ("DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT)
                            , ("DYNAMIC_STATE_FRONT_FACE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_FRONT_FACE_EXT)
                            , ("DYNAMIC_STATE_CULL_MODE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_CULL_MODE_EXT)
                            , ("DYNAMIC_STATE_LINE_STIPPLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_LINE_STIPPLE_EXT)
                            , ("DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV)
                            , ("DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV)
                            , ("DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV)
                            , ("DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT)
                            , ("DYNAMIC_STATE_DISCARD_RECTANGLE_EXT", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_DISCARD_RECTANGLE_EXT)
                            , ("DYNAMIC_STATE_VIEWPORT_W_SCALING_NV", DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure DynamicState
DYNAMIC_STATE_VIEWPORT_W_SCALING_NV)]
                     ReadPrec DynamicState
-> ReadPrec DynamicState -> ReadPrec DynamicState
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec DynamicState -> ReadPrec DynamicState
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DynamicState")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       DynamicState -> ReadPrec DynamicState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> DynamicState
DynamicState Int32
v)))