{-# language CPP #-}
module Vulkan.Core10.Enums.ImageLayout  (ImageLayout( IMAGE_LAYOUT_UNDEFINED
                                                    , IMAGE_LAYOUT_GENERAL
                                                    , IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL
                                                    , IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL
                                                    , IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL
                                                    , IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL
                                                    , IMAGE_LAYOUT_PREINITIALIZED
                                                    , IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT
                                                    , IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV
                                                    , IMAGE_LAYOUT_SHARED_PRESENT_KHR
                                                    , IMAGE_LAYOUT_PRESENT_SRC_KHR
                                                    , IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
                                                    , IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL
                                                    , IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
                                                    , ..
                                                    )) 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)
-- | VkImageLayout - Layout of image and image subresources
--
-- = Description
--
-- The type(s) of device access supported by each layout are:
--
-- The layout of each image subresource is not a state of the image
-- subresource itself, but is rather a property of how the data in memory
-- is organized, and thus for each mechanism of accessing an image in the
-- API the application /must/ specify a parameter or structure member that
-- indicates which image layout the image subresource(s) are considered to
-- be in when the image will be accessed. For transfer commands, this is a
-- parameter to the command (see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears>
-- and
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies>).
-- For use as a framebuffer attachment, this is a member in the
-- substructures of the 'Vulkan.Core10.Pass.RenderPassCreateInfo' (see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass Render Pass>).
-- For use in a descriptor set, this is a member in the
-- 'Vulkan.Core10.DescriptorSet.DescriptorImageInfo' structure (see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-updates>).
--
-- = See Also
--
-- 'Vulkan.Core10.Pass.AttachmentDescription',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout',
-- 'Vulkan.Core10.Pass.AttachmentReference',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentReference2',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentReferenceStencilLayout',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.BlitImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyBufferToImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyImageToBufferInfo2KHR',
-- 'Vulkan.Core10.DescriptorSet.DescriptorImageInfo',
-- 'Vulkan.Core10.Image.ImageCreateInfo',
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.ResolveImageInfo2KHR',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdBindShadingRateImageNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResolveImage'
newtype ImageLayout = ImageLayout Int32
  deriving newtype (ImageLayout -> ImageLayout -> Bool
(ImageLayout -> ImageLayout -> Bool)
-> (ImageLayout -> ImageLayout -> Bool) -> Eq ImageLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageLayout -> ImageLayout -> Bool
$c/= :: ImageLayout -> ImageLayout -> Bool
== :: ImageLayout -> ImageLayout -> Bool
$c== :: ImageLayout -> ImageLayout -> Bool
Eq, Eq ImageLayout
Eq ImageLayout =>
(ImageLayout -> ImageLayout -> Ordering)
-> (ImageLayout -> ImageLayout -> Bool)
-> (ImageLayout -> ImageLayout -> Bool)
-> (ImageLayout -> ImageLayout -> Bool)
-> (ImageLayout -> ImageLayout -> Bool)
-> (ImageLayout -> ImageLayout -> ImageLayout)
-> (ImageLayout -> ImageLayout -> ImageLayout)
-> Ord ImageLayout
ImageLayout -> ImageLayout -> Bool
ImageLayout -> ImageLayout -> Ordering
ImageLayout -> ImageLayout -> ImageLayout
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 :: ImageLayout -> ImageLayout -> ImageLayout
$cmin :: ImageLayout -> ImageLayout -> ImageLayout
max :: ImageLayout -> ImageLayout -> ImageLayout
$cmax :: ImageLayout -> ImageLayout -> ImageLayout
>= :: ImageLayout -> ImageLayout -> Bool
$c>= :: ImageLayout -> ImageLayout -> Bool
> :: ImageLayout -> ImageLayout -> Bool
$c> :: ImageLayout -> ImageLayout -> Bool
<= :: ImageLayout -> ImageLayout -> Bool
$c<= :: ImageLayout -> ImageLayout -> Bool
< :: ImageLayout -> ImageLayout -> Bool
$c< :: ImageLayout -> ImageLayout -> Bool
compare :: ImageLayout -> ImageLayout -> Ordering
$ccompare :: ImageLayout -> ImageLayout -> Ordering
$cp1Ord :: Eq ImageLayout
Ord, Ptr b -> Int -> IO ImageLayout
Ptr b -> Int -> ImageLayout -> IO ()
Ptr ImageLayout -> IO ImageLayout
Ptr ImageLayout -> Int -> IO ImageLayout
Ptr ImageLayout -> Int -> ImageLayout -> IO ()
Ptr ImageLayout -> ImageLayout -> IO ()
ImageLayout -> Int
(ImageLayout -> Int)
-> (ImageLayout -> Int)
-> (Ptr ImageLayout -> Int -> IO ImageLayout)
-> (Ptr ImageLayout -> Int -> ImageLayout -> IO ())
-> (forall b. Ptr b -> Int -> IO ImageLayout)
-> (forall b. Ptr b -> Int -> ImageLayout -> IO ())
-> (Ptr ImageLayout -> IO ImageLayout)
-> (Ptr ImageLayout -> ImageLayout -> IO ())
-> Storable ImageLayout
forall b. Ptr b -> Int -> IO ImageLayout
forall b. Ptr b -> Int -> ImageLayout -> 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 ImageLayout -> ImageLayout -> IO ()
$cpoke :: Ptr ImageLayout -> ImageLayout -> IO ()
peek :: Ptr ImageLayout -> IO ImageLayout
$cpeek :: Ptr ImageLayout -> IO ImageLayout
pokeByteOff :: Ptr b -> Int -> ImageLayout -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ImageLayout -> IO ()
peekByteOff :: Ptr b -> Int -> IO ImageLayout
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ImageLayout
pokeElemOff :: Ptr ImageLayout -> Int -> ImageLayout -> IO ()
$cpokeElemOff :: Ptr ImageLayout -> Int -> ImageLayout -> IO ()
peekElemOff :: Ptr ImageLayout -> Int -> IO ImageLayout
$cpeekElemOff :: Ptr ImageLayout -> Int -> IO ImageLayout
alignment :: ImageLayout -> Int
$calignment :: ImageLayout -> Int
sizeOf :: ImageLayout -> Int
$csizeOf :: ImageLayout -> Int
Storable, ImageLayout
ImageLayout -> Zero ImageLayout
forall a. a -> Zero a
zero :: ImageLayout
$czero :: ImageLayout
Zero)

-- | 'IMAGE_LAYOUT_UNDEFINED' does not support device access. This layout
-- /must/ only be used as the @initialLayout@ member of
-- 'Vulkan.Core10.Image.ImageCreateInfo' or
-- 'Vulkan.Core10.Pass.AttachmentDescription', or as the @oldLayout@ in an
-- image transition. When transitioning out of this layout, the contents of
-- the memory are not guaranteed to be preserved.
pattern $bIMAGE_LAYOUT_UNDEFINED :: ImageLayout
$mIMAGE_LAYOUT_UNDEFINED :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_UNDEFINED = ImageLayout 0
-- | 'IMAGE_LAYOUT_GENERAL' supports all types of device access.
pattern $bIMAGE_LAYOUT_GENERAL :: ImageLayout
$mIMAGE_LAYOUT_GENERAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_GENERAL = ImageLayout 1
-- | 'IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL' /must/ only be used as a color
-- or resolve attachment in a 'Vulkan.Core10.Handles.Framebuffer'. This
-- layout is valid only for image subresources of images created with the
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT'
-- usage bit enabled.
pattern $bIMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL = ImageLayout 2
-- | 'IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' specifies a layout for
-- both the depth and stencil aspects of a depth\/stencil format image
-- allowing read and write access as a depth\/stencil attachment. It is
-- equivalent to 'IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' and
-- 'IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'.
pattern $bIMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL = ImageLayout 3
-- | 'IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL' specifies a layout for
-- both the depth and stencil aspects of a depth\/stencil format image
-- allowing read only access as a depth\/stencil attachment or in shaders
-- as a sampled image, combined image\/sampler, or input attachment. It is
-- equivalent to 'IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' and
-- 'IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'.
pattern $bIMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL = ImageLayout 4
-- | 'IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' specifies a layout allowing
-- read-only access in a shader as a sampled image, combined
-- image\/sampler, or input attachment. This layout is valid only for image
-- subresources of images created with the
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT' or
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
-- usage bit enabled.
pattern $bIMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL = ImageLayout 5
-- | 'IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL' /must/ only be used as a source
-- image of a transfer command (see the definition of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-transfer >).
-- This layout is valid only for image subresources of images created with
-- the
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
-- usage bit enabled.
pattern $bIMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL = ImageLayout 6
-- | 'IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL' /must/ only be used as a destination
-- image of a transfer command. This layout is valid only for image
-- subresources of images created with the
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
-- usage bit enabled.
pattern $bIMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL = ImageLayout 7
-- | 'IMAGE_LAYOUT_PREINITIALIZED' does not support device access. This
-- layout /must/ only be used as the @initialLayout@ member of
-- 'Vulkan.Core10.Image.ImageCreateInfo' or
-- 'Vulkan.Core10.Pass.AttachmentDescription', or as the @oldLayout@ in an
-- image transition. When transitioning out of this layout, the contents of
-- the memory are preserved. This layout is intended to be used as the
-- initial layout for an image whose contents are written by the host, and
-- hence the data /can/ be written to memory immediately, without first
-- executing a layout transition. Currently, 'IMAGE_LAYOUT_PREINITIALIZED'
-- is only useful with
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#glossary-linear-resource linear>
-- images because there is not a standard layout defined for
-- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_OPTIMAL' images.
pattern $bIMAGE_LAYOUT_PREINITIALIZED :: ImageLayout
$mIMAGE_LAYOUT_PREINITIALIZED :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_PREINITIALIZED = ImageLayout 8
-- | 'IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT' /must/ only be used as a
-- fragment density map attachment in a 'Vulkan.Core10.Handles.RenderPass'.
-- This layout is valid only for image subresources of images created with
-- the
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT'
-- usage bit enabled.
pattern $bIMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT :: ImageLayout
$mIMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT = ImageLayout 1000218000
-- No documentation found for Nested "VkImageLayout" "VK_IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV"
pattern $bIMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV :: ImageLayout
$mIMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV = ImageLayout 1000164003
-- | 'IMAGE_LAYOUT_SHARED_PRESENT_KHR' is valid only for shared presentable
-- images, and /must/ be used for any usage the image supports.
pattern $bIMAGE_LAYOUT_SHARED_PRESENT_KHR :: ImageLayout
$mIMAGE_LAYOUT_SHARED_PRESENT_KHR :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_SHARED_PRESENT_KHR = ImageLayout 1000111000
-- | 'IMAGE_LAYOUT_PRESENT_SRC_KHR' /must/ only be used for presenting a
-- presentable image for display. A swapchain’s image /must/ be
-- transitioned to this layout before calling
-- 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR', and /must/ be
-- transitioned away from this layout after calling
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR'.
pattern $bIMAGE_LAYOUT_PRESENT_SRC_KHR :: ImageLayout
$mIMAGE_LAYOUT_PRESENT_SRC_KHR :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_PRESENT_SRC_KHR = ImageLayout 1000001002
-- | 'IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' specifies a layout for the
-- stencil aspect of a depth\/stencil format image allowing read-only
-- access as a stencil attachment or in shaders as a sampled image,
-- combined image\/sampler, or input attachment.
pattern $bIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL = ImageLayout 1000241003
-- | 'IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' specifies a layout for the
-- stencil aspect of a depth\/stencil format image allowing read and write
-- access as a stencil attachment.
pattern $bIMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL = ImageLayout 1000241002
-- | 'IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' specifies a layout for the depth
-- aspect of a depth\/stencil format image allowing read-only access as a
-- depth attachment or in shaders as a sampled image, combined
-- image\/sampler, or input attachment.
pattern $bIMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL = ImageLayout 1000241001
-- | 'IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' specifies a layout for the depth
-- aspect of a depth\/stencil format image allowing read and write access
-- as a depth attachment.
pattern $bIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL = ImageLayout 1000241000
-- | 'IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' specifies a
-- layout for depth\/stencil format images allowing read and write access
-- to the depth aspect as a depth attachment, and read only access to the
-- stencil aspect as a stencil attachment or in shaders as a sampled image,
-- combined image\/sampler, or input attachment. It is equivalent to
-- 'IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' and
-- 'IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'.
pattern $bIMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL = ImageLayout 1000117001
-- | 'IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' specifies a
-- layout for depth\/stencil format images allowing read and write access
-- to the stencil aspect as a stencil attachment, and read only access to
-- the depth aspect as a depth attachment or in shaders as a sampled image,
-- combined image\/sampler, or input attachment. It is equivalent to
-- 'IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' and
-- 'IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'.
pattern $bIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout
$mIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL :: forall r. ImageLayout -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL = ImageLayout 1000117000
{-# complete IMAGE_LAYOUT_UNDEFINED,
             IMAGE_LAYOUT_GENERAL,
             IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL,
             IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL,
             IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL,
             IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL,
             IMAGE_LAYOUT_PREINITIALIZED,
             IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT,
             IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV,
             IMAGE_LAYOUT_SHARED_PRESENT_KHR,
             IMAGE_LAYOUT_PRESENT_SRC_KHR,
             IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL,
             IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL,
             IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout #-}

instance Show ImageLayout where
  showsPrec :: Int -> ImageLayout -> ShowS
showsPrec p :: Int
p = \case
    IMAGE_LAYOUT_UNDEFINED -> String -> ShowS
showString "IMAGE_LAYOUT_UNDEFINED"
    IMAGE_LAYOUT_GENERAL -> String -> ShowS
showString "IMAGE_LAYOUT_GENERAL"
    IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL"
    IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL"
    IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL"
    IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL"
    IMAGE_LAYOUT_PREINITIALIZED -> String -> ShowS
showString "IMAGE_LAYOUT_PREINITIALIZED"
    IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT -> String -> ShowS
showString "IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT"
    IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV -> String -> ShowS
showString "IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV"
    IMAGE_LAYOUT_SHARED_PRESENT_KHR -> String -> ShowS
showString "IMAGE_LAYOUT_SHARED_PRESENT_KHR"
    IMAGE_LAYOUT_PRESENT_SRC_KHR -> String -> ShowS
showString "IMAGE_LAYOUT_PRESENT_SRC_KHR"
    IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL"
    IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL"
    IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL -> String -> ShowS
showString "IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL"
    ImageLayout x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ImageLayout " 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 ImageLayout where
  readPrec :: ReadPrec ImageLayout
readPrec = ReadPrec ImageLayout -> ReadPrec ImageLayout
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ImageLayout)] -> ReadPrec ImageLayout
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("IMAGE_LAYOUT_UNDEFINED", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_UNDEFINED)
                            , ("IMAGE_LAYOUT_GENERAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_GENERAL)
                            , ("IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL)
                            , ("IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL)
                            , ("IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL)
                            , ("IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL)
                            , ("IMAGE_LAYOUT_PREINITIALIZED", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_PREINITIALIZED)
                            , ("IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT)
                            , ("IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV)
                            , ("IMAGE_LAYOUT_SHARED_PRESENT_KHR", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_SHARED_PRESENT_KHR)
                            , ("IMAGE_LAYOUT_PRESENT_SRC_KHR", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_PRESENT_SRC_KHR)
                            , ("IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL)
                            , ("IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL)
                            , ("IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL", ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageLayout
IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL)]
                     ReadPrec ImageLayout
-> ReadPrec ImageLayout -> ReadPrec ImageLayout
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec ImageLayout -> ReadPrec ImageLayout
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ImageLayout")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       ImageLayout -> ReadPrec ImageLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> ImageLayout
ImageLayout Int32
v)))