{-# language CPP #-}
module Vulkan.Core10.Enums.SamplerCreateFlagBits ( SamplerCreateFlags
, SamplerCreateFlagBits( SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM
, SAMPLER_CREATE_NON_SEAMLESS_CUBE_MAP_BIT_EXT
, SAMPLER_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT
, SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT
, SAMPLER_CREATE_SUBSAMPLED_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 SamplerCreateFlags = SamplerCreateFlagBits
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
$c== :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
== :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$c/= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
/= :: 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
$ccompare :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering
compare :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Ordering
$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
>= :: SamplerCreateFlagBits -> SamplerCreateFlagBits -> Bool
$cmax :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
max :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cmin :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
min :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
Ord, 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
$csizeOf :: SamplerCreateFlagBits -> Int
sizeOf :: SamplerCreateFlagBits -> Int
$calignment :: SamplerCreateFlagBits -> Int
alignment :: SamplerCreateFlagBits -> Int
$cpeekElemOff :: Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits
peekElemOff :: Ptr SamplerCreateFlagBits -> Int -> IO SamplerCreateFlagBits
$cpokeElemOff :: Ptr SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits -> IO ()
pokeElemOff :: Ptr SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SamplerCreateFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO SamplerCreateFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> SamplerCreateFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> SamplerCreateFlagBits -> IO ()
$cpeek :: Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits
peek :: Ptr SamplerCreateFlagBits -> IO SamplerCreateFlagBits
$cpoke :: Ptr SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ()
poke :: Ptr SamplerCreateFlagBits -> SamplerCreateFlagBits -> IO ()
Storable, SamplerCreateFlagBits
SamplerCreateFlagBits -> Zero SamplerCreateFlagBits
forall a. a -> Zero a
$czero :: SamplerCreateFlagBits
zero :: 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
$c.&. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
.&. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$c.|. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
.|. :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$cxor :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
xor :: SamplerCreateFlagBits
-> SamplerCreateFlagBits -> SamplerCreateFlagBits
$ccomplement :: SamplerCreateFlagBits -> SamplerCreateFlagBits
complement :: SamplerCreateFlagBits -> SamplerCreateFlagBits
$cshift :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shift :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotate :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
rotate :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$czeroBits :: SamplerCreateFlagBits
zeroBits :: SamplerCreateFlagBits
$cbit :: Int -> SamplerCreateFlagBits
bit :: Int -> SamplerCreateFlagBits
$csetBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
setBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cclearBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
clearBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$ccomplementBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
complementBit :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$ctestBit :: SamplerCreateFlagBits -> Int -> Bool
testBit :: SamplerCreateFlagBits -> Int -> Bool
$cbitSizeMaybe :: SamplerCreateFlagBits -> Maybe Int
bitSizeMaybe :: SamplerCreateFlagBits -> Maybe Int
$cbitSize :: SamplerCreateFlagBits -> Int
bitSize :: SamplerCreateFlagBits -> Int
$cisSigned :: SamplerCreateFlagBits -> Bool
isSigned :: SamplerCreateFlagBits -> Bool
$cshiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cunsafeShiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
unsafeShiftL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cshiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
shiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cunsafeShiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
unsafeShiftR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotateL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
rotateL :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$crotateR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
rotateR :: SamplerCreateFlagBits -> Int -> SamplerCreateFlagBits
$cpopCount :: SamplerCreateFlagBits -> Int
popCount :: SamplerCreateFlagBits -> Int
Bits, Bits SamplerCreateFlagBits
Bits SamplerCreateFlagBits =>
(SamplerCreateFlagBits -> Int)
-> (SamplerCreateFlagBits -> Int)
-> (SamplerCreateFlagBits -> Int)
-> FiniteBits SamplerCreateFlagBits
SamplerCreateFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: SamplerCreateFlagBits -> Int
finiteBitSize :: SamplerCreateFlagBits -> Int
$ccountLeadingZeros :: SamplerCreateFlagBits -> Int
countLeadingZeros :: SamplerCreateFlagBits -> Int
$ccountTrailingZeros :: SamplerCreateFlagBits -> Int
countTrailingZeros :: SamplerCreateFlagBits -> Int
FiniteBits)
pattern $bSAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM :: SamplerCreateFlagBits
$mSAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM :: forall {r}.
SamplerCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM = SamplerCreateFlagBits 0x00000010
pattern $bSAMPLER_CREATE_NON_SEAMLESS_CUBE_MAP_BIT_EXT :: SamplerCreateFlagBits
$mSAMPLER_CREATE_NON_SEAMLESS_CUBE_MAP_BIT_EXT :: forall {r}.
SamplerCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
SAMPLER_CREATE_NON_SEAMLESS_CUBE_MAP_BIT_EXT = SamplerCreateFlagBits 0x00000004
pattern $bSAMPLER_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: SamplerCreateFlagBits
$mSAMPLER_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: forall {r}.
SamplerCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
SAMPLER_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT = SamplerCreateFlagBits 0x00000008
pattern $bSAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT :: SamplerCreateFlagBits
$mSAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT :: forall {r}.
SamplerCreateFlagBits -> ((# #) -> r) -> ((# #) -> 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 -> ((# #) -> r) -> ((# #) -> r) -> r
SAMPLER_CREATE_SUBSAMPLED_BIT_EXT = SamplerCreateFlagBits 0x00000001
conNameSamplerCreateFlagBits :: String
conNameSamplerCreateFlagBits :: String
conNameSamplerCreateFlagBits = String
"SamplerCreateFlagBits"
enumPrefixSamplerCreateFlagBits :: String
enumPrefixSamplerCreateFlagBits :: String
enumPrefixSamplerCreateFlagBits = String
"SAMPLER_CREATE_"
showTableSamplerCreateFlagBits :: [(SamplerCreateFlagBits, String)]
showTableSamplerCreateFlagBits :: [(SamplerCreateFlagBits, String)]
showTableSamplerCreateFlagBits =
[
( SamplerCreateFlagBits
SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM
, String
"IMAGE_PROCESSING_BIT_QCOM"
)
,
( SamplerCreateFlagBits
SAMPLER_CREATE_NON_SEAMLESS_CUBE_MAP_BIT_EXT
, String
"NON_SEAMLESS_CUBE_MAP_BIT_EXT"
)
,
( SamplerCreateFlagBits
SAMPLER_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT
, String
"DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT"
)
,
( SamplerCreateFlagBits
SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT
, String
"SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT"
)
,
( SamplerCreateFlagBits
SAMPLER_CREATE_SUBSAMPLED_BIT_EXT
, String
"SUBSAMPLED_BIT_EXT"
)
]
instance Show SamplerCreateFlagBits where
showsPrec :: Int -> SamplerCreateFlagBits -> ShowS
showsPrec =
String
-> [(SamplerCreateFlagBits, String)]
-> String
-> (SamplerCreateFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> SamplerCreateFlagBits
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixSamplerCreateFlagBits
[(SamplerCreateFlagBits, String)]
showTableSamplerCreateFlagBits
String
conNameSamplerCreateFlagBits
(\(SamplerCreateFlagBits 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 SamplerCreateFlagBits where
readPrec :: ReadPrec SamplerCreateFlagBits
readPrec =
String
-> [(SamplerCreateFlagBits, String)]
-> String
-> (Flags -> SamplerCreateFlagBits)
-> ReadPrec SamplerCreateFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixSamplerCreateFlagBits
[(SamplerCreateFlagBits, String)]
showTableSamplerCreateFlagBits
String
conNameSamplerCreateFlagBits
Flags -> SamplerCreateFlagBits
SamplerCreateFlagBits