{-# language CPP #-}
-- No documentation found for Chapter "SubpassContents"
module Vulkan.Core10.Enums.SubpassContents  (SubpassContents( SUBPASS_CONTENTS_INLINE
                                                            , SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS
                                                            , ..
                                                            )) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showsPrec)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))

-- | VkSubpassContents - Specify how commands in the first subpass of a
-- render pass are provided
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.SubpassBeginInfo',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginRenderPass',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdNextSubpass'
newtype SubpassContents = SubpassContents Int32
  deriving newtype (SubpassContents -> SubpassContents -> Bool
(SubpassContents -> SubpassContents -> Bool)
-> (SubpassContents -> SubpassContents -> Bool)
-> Eq SubpassContents
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubpassContents -> SubpassContents -> Bool
$c/= :: SubpassContents -> SubpassContents -> Bool
== :: SubpassContents -> SubpassContents -> Bool
$c== :: SubpassContents -> SubpassContents -> Bool
Eq, Eq SubpassContents
Eq SubpassContents
-> (SubpassContents -> SubpassContents -> Ordering)
-> (SubpassContents -> SubpassContents -> Bool)
-> (SubpassContents -> SubpassContents -> Bool)
-> (SubpassContents -> SubpassContents -> Bool)
-> (SubpassContents -> SubpassContents -> Bool)
-> (SubpassContents -> SubpassContents -> SubpassContents)
-> (SubpassContents -> SubpassContents -> SubpassContents)
-> Ord SubpassContents
SubpassContents -> SubpassContents -> Bool
SubpassContents -> SubpassContents -> Ordering
SubpassContents -> SubpassContents -> SubpassContents
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 :: SubpassContents -> SubpassContents -> SubpassContents
$cmin :: SubpassContents -> SubpassContents -> SubpassContents
max :: SubpassContents -> SubpassContents -> SubpassContents
$cmax :: SubpassContents -> SubpassContents -> SubpassContents
>= :: SubpassContents -> SubpassContents -> Bool
$c>= :: SubpassContents -> SubpassContents -> Bool
> :: SubpassContents -> SubpassContents -> Bool
$c> :: SubpassContents -> SubpassContents -> Bool
<= :: SubpassContents -> SubpassContents -> Bool
$c<= :: SubpassContents -> SubpassContents -> Bool
< :: SubpassContents -> SubpassContents -> Bool
$c< :: SubpassContents -> SubpassContents -> Bool
compare :: SubpassContents -> SubpassContents -> Ordering
$ccompare :: SubpassContents -> SubpassContents -> Ordering
$cp1Ord :: Eq SubpassContents
Ord, Ptr b -> Int -> IO SubpassContents
Ptr b -> Int -> SubpassContents -> IO ()
Ptr SubpassContents -> IO SubpassContents
Ptr SubpassContents -> Int -> IO SubpassContents
Ptr SubpassContents -> Int -> SubpassContents -> IO ()
Ptr SubpassContents -> SubpassContents -> IO ()
SubpassContents -> Int
(SubpassContents -> Int)
-> (SubpassContents -> Int)
-> (Ptr SubpassContents -> Int -> IO SubpassContents)
-> (Ptr SubpassContents -> Int -> SubpassContents -> IO ())
-> (forall b. Ptr b -> Int -> IO SubpassContents)
-> (forall b. Ptr b -> Int -> SubpassContents -> IO ())
-> (Ptr SubpassContents -> IO SubpassContents)
-> (Ptr SubpassContents -> SubpassContents -> IO ())
-> Storable SubpassContents
forall b. Ptr b -> Int -> IO SubpassContents
forall b. Ptr b -> Int -> SubpassContents -> 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 SubpassContents -> SubpassContents -> IO ()
$cpoke :: Ptr SubpassContents -> SubpassContents -> IO ()
peek :: Ptr SubpassContents -> IO SubpassContents
$cpeek :: Ptr SubpassContents -> IO SubpassContents
pokeByteOff :: Ptr b -> Int -> SubpassContents -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SubpassContents -> IO ()
peekByteOff :: Ptr b -> Int -> IO SubpassContents
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SubpassContents
pokeElemOff :: Ptr SubpassContents -> Int -> SubpassContents -> IO ()
$cpokeElemOff :: Ptr SubpassContents -> Int -> SubpassContents -> IO ()
peekElemOff :: Ptr SubpassContents -> Int -> IO SubpassContents
$cpeekElemOff :: Ptr SubpassContents -> Int -> IO SubpassContents
alignment :: SubpassContents -> Int
$calignment :: SubpassContents -> Int
sizeOf :: SubpassContents -> Int
$csizeOf :: SubpassContents -> Int
Storable, SubpassContents
SubpassContents -> Zero SubpassContents
forall a. a -> Zero a
zero :: SubpassContents
$czero :: SubpassContents
Zero)

-- | 'SUBPASS_CONTENTS_INLINE' specifies that the contents of the subpass
-- will be recorded inline in the primary command buffer, and secondary
-- command buffers /must/ not be executed within the subpass.
pattern $bSUBPASS_CONTENTS_INLINE :: SubpassContents
$mSUBPASS_CONTENTS_INLINE :: forall r. SubpassContents -> (Void# -> r) -> (Void# -> r) -> r
SUBPASS_CONTENTS_INLINE                    = SubpassContents 0
-- | 'SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS' specifies that the contents
-- are recorded in secondary command buffers that will be called from the
-- primary command buffer, and
-- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands' is the only
-- valid command on the command buffer until
-- 'Vulkan.Core10.CommandBufferBuilding.cmdNextSubpass' or
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndRenderPass'.
pattern $bSUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS :: SubpassContents
$mSUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS :: forall r. SubpassContents -> (Void# -> r) -> (Void# -> r) -> r
SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS = SubpassContents 1
{-# complete SUBPASS_CONTENTS_INLINE,
             SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS :: SubpassContents #-}

conNameSubpassContents :: String
conNameSubpassContents :: String
conNameSubpassContents = String
"SubpassContents"

enumPrefixSubpassContents :: String
enumPrefixSubpassContents :: String
enumPrefixSubpassContents = String
"SUBPASS_CONTENTS_"

showTableSubpassContents :: [(SubpassContents, String)]
showTableSubpassContents :: [(SubpassContents, String)]
showTableSubpassContents =
  [(SubpassContents
SUBPASS_CONTENTS_INLINE, String
"INLINE"), (SubpassContents
SUBPASS_CONTENTS_SECONDARY_COMMAND_BUFFERS, String
"SECONDARY_COMMAND_BUFFERS")]

instance Show SubpassContents where
  showsPrec :: Int -> SubpassContents -> ShowS
showsPrec = String
-> [(SubpassContents, String)]
-> String
-> (SubpassContents -> Int32)
-> (Int32 -> ShowS)
-> Int
-> SubpassContents
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixSubpassContents
                            [(SubpassContents, String)]
showTableSubpassContents
                            String
conNameSubpassContents
                            (\(SubpassContents Int32
x) -> Int32
x)
                            (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read SubpassContents where
  readPrec :: ReadPrec SubpassContents
readPrec = String
-> [(SubpassContents, String)]
-> String
-> (Int32 -> SubpassContents)
-> ReadPrec SubpassContents
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixSubpassContents [(SubpassContents, String)]
showTableSubpassContents String
conNameSubpassContents Int32 -> SubpassContents
SubpassContents