{-# language CPP #-}
module Vulkan.Core10.Enums.ImageViewCreateFlagBits  ( ImageViewCreateFlagBits( IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT
                                                                             , IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT
                                                                             , ..
                                                                             )
                                                    , ImageViewCreateFlags
                                                    ) 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)
-- | VkImageViewCreateFlagBits - Bitmask specifying additional parameters of
-- an image view
--
-- = See Also
--
-- '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
/= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c/= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
== :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$c== :: 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
min :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cmin :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
max :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cmax :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
>= :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Bool
$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
compare :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering
$ccompare :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> Ordering
$cp1Ord :: Eq ImageViewCreateFlagBits
Ord, Ptr b -> Int -> IO ImageViewCreateFlagBits
Ptr b -> Int -> ImageViewCreateFlagBits -> IO ()
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
poke :: Ptr ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> IO ()
$cpoke :: Ptr ImageViewCreateFlagBits -> ImageViewCreateFlagBits -> IO ()
peek :: Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits
$cpeek :: Ptr ImageViewCreateFlagBits -> IO ImageViewCreateFlagBits
pokeByteOff :: Ptr b -> Int -> ImageViewCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ImageViewCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO ImageViewCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ImageViewCreateFlagBits
pokeElemOff :: Ptr ImageViewCreateFlagBits
-> Int -> ImageViewCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr ImageViewCreateFlagBits
-> Int -> ImageViewCreateFlagBits -> IO ()
peekElemOff :: Ptr ImageViewCreateFlagBits -> Int -> IO ImageViewCreateFlagBits
$cpeekElemOff :: Ptr ImageViewCreateFlagBits -> Int -> IO ImageViewCreateFlagBits
alignment :: ImageViewCreateFlagBits -> Int
$calignment :: ImageViewCreateFlagBits -> Int
sizeOf :: ImageViewCreateFlagBits -> Int
$csizeOf :: ImageViewCreateFlagBits -> Int
Storable, ImageViewCreateFlagBits
ImageViewCreateFlagBits -> Zero ImageViewCreateFlagBits
forall a. a -> Zero a
zero :: ImageViewCreateFlagBits
$czero :: 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
popCount :: ImageViewCreateFlagBits -> Int
$cpopCount :: ImageViewCreateFlagBits -> Int
rotateR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotateR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
rotateL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotateL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
unsafeShiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cunsafeShiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cshiftR :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
unsafeShiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cunsafeShiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cshiftL :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
isSigned :: ImageViewCreateFlagBits -> Bool
$cisSigned :: ImageViewCreateFlagBits -> Bool
bitSize :: ImageViewCreateFlagBits -> Int
$cbitSize :: ImageViewCreateFlagBits -> Int
bitSizeMaybe :: ImageViewCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: ImageViewCreateFlagBits -> Maybe Int
testBit :: ImageViewCreateFlagBits -> Int -> Bool
$ctestBit :: ImageViewCreateFlagBits -> Int -> Bool
complementBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$ccomplementBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
clearBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cclearBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
setBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$csetBit :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
bit :: Int -> ImageViewCreateFlagBits
$cbit :: Int -> ImageViewCreateFlagBits
zeroBits :: ImageViewCreateFlagBits
$czeroBits :: ImageViewCreateFlagBits
rotate :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$crotate :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
shift :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
$cshift :: ImageViewCreateFlagBits -> Int -> ImageViewCreateFlagBits
complement :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$ccomplement :: ImageViewCreateFlagBits -> ImageViewCreateFlagBits
xor :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cxor :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
.|. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$c.|. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
.&. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$c.&. :: ImageViewCreateFlagBits
-> ImageViewCreateFlagBits -> ImageViewCreateFlagBits
$cp1Bits :: Eq ImageViewCreateFlagBits
Bits)

-- | '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 -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT = ImageViewCreateFlagBits 0x00000002
-- | '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 -> (Void# -> r) -> (Void# -> r) -> r
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT = ImageViewCreateFlagBits 0x00000001

type ImageViewCreateFlags = ImageViewCreateFlagBits

instance Show ImageViewCreateFlagBits where
  showsPrec :: Int -> ImageViewCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
    IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT -> String -> ShowS
showString "IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT"
    IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT -> String -> ShowS
showString "IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT"
    ImageViewCreateFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ImageViewCreateFlagBits 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 ImageViewCreateFlagBits where
  readPrec :: ReadPrec ImageViewCreateFlagBits
readPrec = ReadPrec ImageViewCreateFlagBits
-> ReadPrec ImageViewCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ImageViewCreateFlagBits)]
-> ReadPrec ImageViewCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT", ImageViewCreateFlagBits -> ReadPrec ImageViewCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageViewCreateFlagBits
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT)
                            , ("IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT", ImageViewCreateFlagBits -> ReadPrec ImageViewCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImageViewCreateFlagBits
IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DYNAMIC_BIT_EXT)]
                     ReadPrec ImageViewCreateFlagBits
-> ReadPrec ImageViewCreateFlagBits
-> ReadPrec ImageViewCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec ImageViewCreateFlagBits
-> ReadPrec ImageViewCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ImageViewCreateFlagBits")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       ImageViewCreateFlagBits -> ReadPrec ImageViewCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> ImageViewCreateFlagBits
ImageViewCreateFlagBits Flags
v)))