{-# language CPP #-}
-- No documentation found for Chapter "ImageViewCreateFlagBits"
module Vulkan.Core10.Enums.ImageViewCreateFlagBits  ( ImageViewCreateFlags
                                                    , ImageViewCreateFlagBits( IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT
                                                                             , IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT
                                                                             , IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT
                                                                             , ..
                                                                             )
                                                    ) where

import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
type ImageViewCreateFlags = ImageViewCreateFlagBits

-- | VkImageViewCreateFlagBits - Bitmask specifying additional parameters of
-- an image view
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'ImageViewCreateFlags'
newtype ImageViewCreateFlagBits = ImageViewCreateFlagBits Flags
  deriving newtype (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
(ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> Eq ImageViewCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
== :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c/= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
/= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
Eq, Eq ImageViewCreateFlagBits
Eq ImageViewCreateFlagBits =>
(ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits
    -> ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits
    -> ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> Ord ImageViewCreateFlagBits
ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering
ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
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
$ccompare :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering
compare :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering
$c< :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
< :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c<= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
<= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c> :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
> :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c>= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
>= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$cmax :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
max :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cmin :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
min :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
Ord, Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits
Ptr ImageViewCreateFlagBits -> Int -> IO ImageViewCreateFlagBits
Ptr ImageViewCreateFlagBits
-> Int -> ImageViewCreateFlagBits -> IO ()
Ptr ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> IO ()
ImageViewCreateFlagBits -> Int
(ImageViewCreateFlagBits -> Int)
-> (ImageViewCreateFlagBits -> Int)
-> (Ptr ImageViewCreateFlagBits
    -> Int -> IO ImageViewCreateFlagBits)
-> (Ptr ImageViewCreateFlagBits
    -> Int -> ImageViewCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO ImageViewCreateFlagBits)
-> (forall b. Ptr b -> Int -> ImageViewCreateFlagBits -> IO ())
-> (Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits)
-> (Ptr ImageViewCreateFlagBits
    -> ImageViewCreateFlagBits -> IO ())
-> Storable ImageViewCreateFlagBits
forall b. Ptr b -> Int -> IO ImageViewCreateFlagBits
forall b. Ptr b -> Int -> ImageViewCreateFlagBits -> 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
$csizeOf :: ImageViewCreateFlagBits -> Int
sizeOf :: ImageViewCreateFlagBits -> Int
$calignment :: ImageViewCreateFlagBits -> Int
alignment :: ImageViewCreateFlagBits -> Int
$cpeekElemOff :: Ptr ImageViewCreateFlagBits -> Int -> IO ImageViewCreateFlagBits
peekElemOff :: Ptr ImageViewCreateFlagBits -> Int -> IO ImageViewCreateFlagBits
$cpokeElemOff :: Ptr ImageViewCreateFlagBits
-> Int -> ImageViewCreateFlagBits -> IO ()
pokeElemOff :: Ptr ImageViewCreateFlagBits
-> Int -> ImageViewCreateFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ImageViewCreateFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO ImageViewCreateFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> ImageViewCreateFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> ImageViewCreateFlagBits -> IO ()
$cpeek :: Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits
peek :: Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits
$cpoke :: Ptr ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> IO ()
poke :: Ptr ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> IO ()
Storable, ImageViewCreateFlagBits
ImageViewCreateFlagBits -> Zero ImageViewCreateFlagBits
forall a. a -> Zero a
$czero :: ImageViewCreateFlagBits
zero :: ImageViewCreateFlagBits
Zero, Eq ImageViewCreateFlagBits
ImageViewCreateFlagBits
Eq ImageViewCreateFlagBits =>
(ImageViewCreateFlagBits
 -> ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits
    -> ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits
    -> ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> ImageViewCreateFlagBits
-> (Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> Bool)
-> (ImageViewCreateFlagBits -> Maybe Int)
-> (ImageViewCreateFlagBits -> Int)
-> (ImageViewCreateFlagBits -> Bool)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits)
-> (ImageViewCreateFlagBits -> Int)
-> Bits ImageViewCreateFlagBits
Int -> ImageViewCreateFlagBits
ImageViewCreateFlagBits -> Bool
ImageViewCreateFlagBits -> Int
ImageViewCreateFlagBits -> Maybe Int
ImageViewCreateFlagBits -> ImageViewCreateFlagBits
ImageViewCreateFlagBits -> Int -> Bool
ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
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
$c.&. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
.&. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$c.|. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
.|. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cxor :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
xor :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$ccomplement :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits
complement :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cshift :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shift :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotate :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
rotate :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$czeroBits :: ImageViewCreateFlagBits
zeroBits :: ImageViewCreateFlagBits
$cbit :: Int -> ImageViewCreateFlagBits
bit :: Int -> ImageViewCreateFlagBits
$csetBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
setBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cclearBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
clearBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$ccomplementBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
complementBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$ctestBit :: ImageViewCreateFlagBits -> Int -> Bool
testBit :: ImageViewCreateFlagBits -> Int -> Bool
$cbitSizeMaybe :: ImageViewCreateFlagBits -> Maybe Int
bitSizeMaybe :: ImageViewCreateFlagBits -> Maybe Int
$cbitSize :: ImageViewCreateFlagBits -> Int
bitSize :: ImageViewCreateFlagBits -> Int
$cisSigned :: ImageViewCreateFlagBits -> Bool
isSigned :: ImageViewCreateFlagBits -> Bool
$cshiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cunsafeShiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
unsafeShiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cshiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cunsafeShiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
unsafeShiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotateL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
rotateL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotateR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
rotateR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cpopCount :: ImageViewCreateFlagBits -> Int
popCount :: ImageViewCreateFlagBits -> Int
Bits, Bits ImageViewCreateFlagBits
Bits ImageViewCreateFlagBits =>
(ImageViewCreateFlagBits -> Int)
-> (ImageViewCreateFlagBits -> Int)
-> (ImageViewCreateFlagBits -> Int)
-> FiniteBits ImageViewCreateFlagBits
ImageViewCreateFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: ImageViewCreateFlagBits -> Int
finiteBitSize :: ImageViewCreateFlagBits -> Int
$ccountLeadingZeros :: ImageViewCreateFlagBits -> Int
countLeadingZeros :: ImageViewCreateFlagBits -> Int
$ccountTrailingZeros :: ImageViewCreateFlagBits -> Int
countTrailingZeros :: ImageViewCreateFlagBits -> Int
FiniteBits)

-- | 'IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT' specifies that
-- the fragment density map will be read by the host during
-- 'Vulkan.Core10.CommandBuffer.endCommandBuffer' for the primary command
-- buffer that the render pass is recorded into
pattern $bIMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT :: ImageViewCreateFlagBits
$mIMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT :: forall {r}.
ImageViewCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT = ImageViewCreateFlagBits 0x00000002

-- | 'IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT' specifies
-- that the image view /can/ be used with descriptor buffers when capturing
-- and replaying (e.g. for trace capture and replay), see
-- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.OpaqueCaptureDescriptorDataCreateInfoEXT'
-- for more detail.
pattern $bIMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: ImageViewCreateFlagBits
$mIMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: forall {r}.
ImageViewCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT = ImageViewCreateFlagBits 0x00000004

-- | 'IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT' specifies that
-- the fragment density map will be read by device during
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT'
pattern $bIMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT :: ImageViewCreateFlagBits
$mIMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT :: forall {r}.
ImageViewCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT = ImageViewCreateFlagBits 0x00000001

conNameImageViewCreateFlagBits :: String
conNameImageViewCreateFlagBits :: String
conNameImageViewCreateFlagBits = String
"ImageViewCreateFlagBits"

enumPrefixImageViewCreateFlagBits :: String
enumPrefixImageViewCreateFlagBits :: String
enumPrefixImageViewCreateFlagBits = String
"IMAGE_VIEW_CREATE_"

showTableImageViewCreateFlagBits :: [(ImageViewCreateFlagBits, String)]
showTableImageViewCreateFlagBits :: [(ImageViewCreateFlagBits, String)]
showTableImageViewCreateFlagBits =
  [
    ( ImageViewCreateFlagBits
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT
    , String
"FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT"
    )
  ,
    ( ImageViewCreateFlagBits
IMAGE_VIEW_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT
    , String
"DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT"
    )
  ,
    ( ImageViewCreateFlagBits
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT
    , String
"FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT"
    )
  ]

instance Show ImageViewCreateFlagBits where
  showsPrec :: Int -> ImageViewCreateFlagBits -> ShowS
showsPrec =
    String
-> [(ImageViewCreateFlagBits, String)]
-> String
-> (ImageViewCreateFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> ImageViewCreateFlagBits
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixImageViewCreateFlagBits
      [(ImageViewCreateFlagBits, String)]
showTableImageViewCreateFlagBits
      String
conNameImageViewCreateFlagBits
      (\(ImageViewCreateFlagBits Flags
x) -> Flags
x)
      (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. Integral a => a -> ShowS
showHex Flags
x)

instance Read ImageViewCreateFlagBits where
  readPrec :: ReadPrec ImageViewCreateFlagBits
readPrec =
    String
-> [(ImageViewCreateFlagBits, String)]
-> String
-> (Flags -> ImageViewCreateFlagBits)
-> ReadPrec ImageViewCreateFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixImageViewCreateFlagBits
      [(ImageViewCreateFlagBits, String)]
showTableImageViewCreateFlagBits
      String
conNameImageViewCreateFlagBits
      Flags -> ImageViewCreateFlagBits
ImageViewCreateFlagBits