{-# language CPP #-}
module Vulkan.Core10.Enums.SamplerCreateFlagBits ( SamplerCreateFlagBits( SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT
, SAMPLER_CREATE_SUBSAMPLED_BIT_EXT
, ..
)
, SamplerCreateFlags
) 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)
newtype SamplerCreateFlagBits = SamplerCreateFlagBits Flags
deriving newtype (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
(SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> Eq SamplerCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c/= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
== :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c== :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
Eq, Eq SamplerCreateFlagBits
Eq SamplerCreateFlagBits =>
(SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> Ord SamplerCreateFlagBits
SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering
SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
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 :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cmin :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
max :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cmax :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
>= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c>= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
> :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c> :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
<= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c<= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
< :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c< :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
compare :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering
$ccompare :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering
$cp1Ord :: Eq SamplerCreateFlagBits
Ord, Ptr b -> Int -> IO SamplerCreateFlagBits
Ptr b -> Int -> SamplerCreateFlagBits -> IO ()
Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits
Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits
Ptr SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits -> IO ()
Ptr SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ()
SamplerCreateFlagBits -> Int
(SamplerCreateFlagBits -> Int)
-> (SamplerCreateFlagBits -> Int)
-> (Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits)
-> (Ptr SamplerCreateFlagBits
-> Int -> SamplerCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO SamplerCreateFlagBits)
-> (forall b. Ptr b -> Int -> SamplerCreateFlagBits -> IO ())
-> (Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits)
-> (Ptr SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ())
-> Storable SamplerCreateFlagBits
forall b. Ptr b -> Int -> IO SamplerCreateFlagBits
forall b. Ptr b -> Int -> SamplerCreateFlagBits -> 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 SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ()
$cpoke :: Ptr SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ()
peek :: Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits
$cpeek :: Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits
pokeByteOff :: Ptr b -> Int -> SamplerCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SamplerCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO SamplerCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SamplerCreateFlagBits
pokeElemOff :: Ptr SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits -> IO ()
peekElemOff :: Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits
$cpeekElemOff :: Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits
alignment :: SamplerCreateFlagBits -> Int
$calignment :: SamplerCreateFlagBits -> Int
sizeOf :: SamplerCreateFlagBits -> Int
$csizeOf :: SamplerCreateFlagBits -> Int
Storable, SamplerCreateFlagBits
SamplerCreateFlagBits -> Zero SamplerCreateFlagBits
forall a. a -> Zero a
zero :: SamplerCreateFlagBits
$czero :: SamplerCreateFlagBits
Zero, Eq SamplerCreateFlagBits
SamplerCreateFlagBits
Eq SamplerCreateFlagBits =>
(SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> SamplerCreateFlagBits
-> (Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> Bool)
-> (SamplerCreateFlagBits -> Maybe Int)
-> (SamplerCreateFlagBits -> Int)
-> (SamplerCreateFlagBits -> Bool)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits)
-> (SamplerCreateFlagBits -> Int)
-> Bits SamplerCreateFlagBits
Int -> SamplerCreateFlagBits
SamplerCreateFlagBits -> Bool
SamplerCreateFlagBits -> Int
SamplerCreateFlagBits -> Maybe Int
SamplerCreateFlagBits -> SamplerCreateFlagBits
SamplerCreateFlagBits -> Int -> Bool
SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
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 :: SamplerCreateFlagBits -> Int
$cpopCount :: SamplerCreateFlagBits -> Int
rotateR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotateR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
rotateL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotateL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
unsafeShiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cunsafeShiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cshiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
unsafeShiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cunsafeShiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cshiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
isSigned :: SamplerCreateFlagBits -> Bool
$cisSigned :: SamplerCreateFlagBits -> Bool
bitSize :: SamplerCreateFlagBits -> Int
$cbitSize :: SamplerCreateFlagBits -> Int
bitSizeMaybe :: SamplerCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: SamplerCreateFlagBits -> Maybe Int
testBit :: SamplerCreateFlagBits -> Int -> Bool
$ctestBit :: SamplerCreateFlagBits -> Int -> Bool
complementBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$ccomplementBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
clearBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cclearBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
setBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$csetBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
bit :: Int -> SamplerCreateFlagBits
$cbit :: Int -> SamplerCreateFlagBits
zeroBits :: SamplerCreateFlagBits
$czeroBits :: SamplerCreateFlagBits
rotate :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotate :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shift :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cshift :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
complement :: SamplerCreateFlagBits -> SamplerCreateFlagBits
$ccomplement :: SamplerCreateFlagBits -> SamplerCreateFlagBits
xor :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cxor :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
.|. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$c.|. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
.&. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$c.&. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cp1Bits :: Eq SamplerCreateFlagBits
Bits)
pattern $bSAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT :: SamplerCreateFlagBits
$mSAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT :: forall r.
SamplerCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT = SamplerCreateFlagBits 0x00000002
pattern $bSAMPLER_CREATE_SUBSAMPLED_BIT_EXT :: SamplerCreateFlagBits
$mSAMPLER_CREATE_SUBSAMPLED_BIT_EXT :: forall r.
SamplerCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
SAMPLER_CREATE_SUBSAMPLED_BIT_EXT = SamplerCreateFlagBits 0x00000001
type SamplerCreateFlags = SamplerCreateFlagBits
instance Show SamplerCreateFlagBits where
showsPrec :: Int -> SamplerCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT -> String -> ShowS
showString "SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT"
SAMPLER_CREATE_SUBSAMPLED_BIT_EXT -> String -> ShowS
showString "SAMPLER_CREATE_SUBSAMPLED_BIT_EXT"
SamplerCreateFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SamplerCreateFlagBits 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 SamplerCreateFlagBits where
readPrec :: ReadPrec SamplerCreateFlagBits
readPrec = ReadPrec SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec SamplerCreateFlagBits)]
-> ReadPrec SamplerCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT", SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure SamplerCreateFlagBits
SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT)
, ("SAMPLER_CREATE_SUBSAMPLED_BIT_EXT", SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure SamplerCreateFlagBits
SAMPLER_CREATE_SUBSAMPLED_BIT_EXT)]
ReadPrec SamplerCreateFlagBits
-> ReadPrec SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "SamplerCreateFlagBits")
Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
SamplerCreateFlagBits -> ReadPrec SamplerCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> SamplerCreateFlagBits
SamplerCreateFlagBits Flags
v)))