{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.SampleCountFlags
       (VkSampleCountBitmask(VkSampleCountBitmask, VkSampleCountFlags,
                             VkSampleCountFlagBits, VK_SAMPLE_COUNT_1_BIT,
                             VK_SAMPLE_COUNT_2_BIT, VK_SAMPLE_COUNT_4_BIT,
                             VK_SAMPLE_COUNT_8_BIT, VK_SAMPLE_COUNT_16_BIT,
                             VK_SAMPLE_COUNT_32_BIT, VK_SAMPLE_COUNT_64_BIT),
        VkSampleCountFlags, VkSampleCountFlagBits)
       where
import           Data.Bits                       (Bits, FiniteBits)
import           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
import           GHC.Read                        (choose, expectP)
import           Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType)
import           Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import           Text.ParserCombinators.ReadPrec (prec, step, (+++))
import           Text.Read                       (Read (..), parens)
import           Text.Read.Lex                   (Lexeme (..))

newtype VkSampleCountBitmask (a ::
                                FlagType) = VkSampleCountBitmask VkFlags
                                              deriving (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
(VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> Eq (VkSampleCountBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
/= :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
== :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
Eq, Eq (VkSampleCountBitmask a)
Eq (VkSampleCountBitmask a)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Ordering)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> (VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool)
-> (VkSampleCountBitmask a
    -> VkSampleCountBitmask a -> VkSampleCountBitmask a)
-> (VkSampleCountBitmask a
    -> VkSampleCountBitmask a -> VkSampleCountBitmask a)
-> Ord (VkSampleCountBitmask a)
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Ordering
VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
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
forall (a :: FlagType). Eq (VkSampleCountBitmask a)
forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Ordering
forall (a :: FlagType).
VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
min :: VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
$cmin :: forall (a :: FlagType).
VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
max :: VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
$cmax :: forall (a :: FlagType).
VkSampleCountBitmask a
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
>= :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
> :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
<= :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
< :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Bool
compare :: VkSampleCountBitmask a -> VkSampleCountBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkSampleCountBitmask a -> VkSampleCountBitmask a -> Ordering
$cp1Ord :: forall (a :: FlagType). Eq (VkSampleCountBitmask a)
Ord, Ptr b -> Int -> IO (VkSampleCountBitmask a)
Ptr b -> Int -> VkSampleCountBitmask a -> IO ()
Ptr (VkSampleCountBitmask a) -> IO (VkSampleCountBitmask a)
Ptr (VkSampleCountBitmask a) -> Int -> IO (VkSampleCountBitmask a)
Ptr (VkSampleCountBitmask a)
-> Int -> VkSampleCountBitmask a -> IO ()
Ptr (VkSampleCountBitmask a) -> VkSampleCountBitmask a -> IO ()
VkSampleCountBitmask a -> Int
(VkSampleCountBitmask a -> Int)
-> (VkSampleCountBitmask a -> Int)
-> (Ptr (VkSampleCountBitmask a)
    -> Int -> IO (VkSampleCountBitmask a))
-> (Ptr (VkSampleCountBitmask a)
    -> Int -> VkSampleCountBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkSampleCountBitmask a))
-> (forall b. Ptr b -> Int -> VkSampleCountBitmask a -> IO ())
-> (Ptr (VkSampleCountBitmask a) -> IO (VkSampleCountBitmask a))
-> (Ptr (VkSampleCountBitmask a)
    -> VkSampleCountBitmask a -> IO ())
-> Storable (VkSampleCountBitmask a)
forall b. Ptr b -> Int -> IO (VkSampleCountBitmask a)
forall b. Ptr b -> Int -> VkSampleCountBitmask a -> 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
forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> IO (VkSampleCountBitmask a)
forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> Int -> IO (VkSampleCountBitmask a)
forall (a :: FlagType).
Ptr (VkSampleCountBitmask a)
-> Int -> VkSampleCountBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> VkSampleCountBitmask a -> IO ()
forall (a :: FlagType). VkSampleCountBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSampleCountBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkSampleCountBitmask a -> IO ()
poke :: Ptr (VkSampleCountBitmask a) -> VkSampleCountBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> VkSampleCountBitmask a -> IO ()
peek :: Ptr (VkSampleCountBitmask a) -> IO (VkSampleCountBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> IO (VkSampleCountBitmask a)
pokeByteOff :: Ptr b -> Int -> VkSampleCountBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkSampleCountBitmask a -> IO ()
peekByteOff :: Ptr b -> Int -> IO (VkSampleCountBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkSampleCountBitmask a)
pokeElemOff :: Ptr (VkSampleCountBitmask a)
-> Int -> VkSampleCountBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkSampleCountBitmask a)
-> Int -> VkSampleCountBitmask a -> IO ()
peekElemOff :: Ptr (VkSampleCountBitmask a) -> Int -> IO (VkSampleCountBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkSampleCountBitmask a) -> Int -> IO (VkSampleCountBitmask a)
alignment :: VkSampleCountBitmask a -> Int
$calignment :: forall (a :: FlagType). VkSampleCountBitmask a -> Int
sizeOf :: VkSampleCountBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkSampleCountBitmask a -> Int
Storable, Typeable (VkSampleCountBitmask a)
DataType
Constr
Typeable (VkSampleCountBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkSampleCountBitmask a
    -> c (VkSampleCountBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a))
-> (VkSampleCountBitmask a -> Constr)
-> (VkSampleCountBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkSampleCountBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkSampleCountBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkSampleCountBitmask a -> VkSampleCountBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkSampleCountBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkSampleCountBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkSampleCountBitmask a -> m (VkSampleCountBitmask a))
-> Data (VkSampleCountBitmask a)
VkSampleCountBitmask a -> DataType
VkSampleCountBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkSampleCountBitmask a
-> c (VkSampleCountBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkSampleCountBitmask a)
forall (a :: FlagType).
Typeable a =>
VkSampleCountBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkSampleCountBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkSampleCountBitmask a
-> c (VkSampleCountBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkSampleCountBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkSampleCountBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkSampleCountBitmask a
-> c (VkSampleCountBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VkSampleCountBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkSampleCountBitmask a))
$cVkSampleCountBitmask :: Constr
$tVkSampleCountBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkSampleCountBitmask a -> m (VkSampleCountBitmask a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkSampleCountBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkSampleCountBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkSampleCountBitmask a -> VkSampleCountBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkSampleCountBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkSampleCountBitmask a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (VkSampleCountBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkSampleCountBitmask a))
dataTypeOf :: VkSampleCountBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkSampleCountBitmask a -> DataType
toConstr :: VkSampleCountBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkSampleCountBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkSampleCountBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkSampleCountBitmask a
-> c (VkSampleCountBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkSampleCountBitmask a
-> c (VkSampleCountBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkSampleCountBitmask a)
Data, (forall x.
 VkSampleCountBitmask a -> Rep (VkSampleCountBitmask a) x)
-> (forall x.
    Rep (VkSampleCountBitmask a) x -> VkSampleCountBitmask a)
-> Generic (VkSampleCountBitmask a)
forall x. Rep (VkSampleCountBitmask a) x -> VkSampleCountBitmask a
forall x. VkSampleCountBitmask a -> Rep (VkSampleCountBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkSampleCountBitmask a) x -> VkSampleCountBitmask a
forall (a :: FlagType) x.
VkSampleCountBitmask a -> Rep (VkSampleCountBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkSampleCountBitmask a) x -> VkSampleCountBitmask a
$cfrom :: forall (a :: FlagType) x.
VkSampleCountBitmask a -> Rep (VkSampleCountBitmask a) x
Generic)

type VkSampleCountFlags = VkSampleCountBitmask FlagMask

type VkSampleCountFlagBits = VkSampleCountBitmask FlagBit

pattern VkSampleCountFlagBits ::
        VkFlags -> VkSampleCountBitmask FlagBit

pattern $bVkSampleCountFlagBits :: VkFlags -> VkSampleCountBitmask FlagBit
$mVkSampleCountFlagBits :: forall r.
VkSampleCountBitmask FlagBit -> (VkFlags -> r) -> (Void# -> r) -> r
VkSampleCountFlagBits n = VkSampleCountBitmask n

pattern VkSampleCountFlags ::
        VkFlags -> VkSampleCountBitmask FlagMask

pattern $bVkSampleCountFlags :: VkFlags -> VkSampleCountBitmask FlagMask
$mVkSampleCountFlags :: forall r.
VkSampleCountBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkSampleCountFlags n = VkSampleCountBitmask n

deriving instance Bits (VkSampleCountBitmask FlagMask)

deriving instance FiniteBits (VkSampleCountBitmask FlagMask)

deriving instance Integral (VkSampleCountBitmask FlagMask)

deriving instance Num (VkSampleCountBitmask FlagMask)

deriving instance Bounded (VkSampleCountBitmask FlagMask)

deriving instance Enum (VkSampleCountBitmask FlagMask)

deriving instance Real (VkSampleCountBitmask FlagMask)

instance Show (VkSampleCountBitmask a) where
        showsPrec :: Int -> VkSampleCountBitmask a -> ShowS
showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_1_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_1_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_2_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_2_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_4_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_4_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_8_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_8_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_16_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_16_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_32_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_32_BIT"
        showsPrec Int
_ VkSampleCountBitmask a
VK_SAMPLE_COUNT_64_BIT
          = String -> ShowS
showString String
"VK_SAMPLE_COUNT_64_BIT"
        showsPrec Int
p (VkSampleCountBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkSampleCountBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkSampleCountBitmask a) where
        readPrec :: ReadPrec (VkSampleCountBitmask a)
readPrec
          = ReadPrec (VkSampleCountBitmask a)
-> ReadPrec (VkSampleCountBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkSampleCountBitmask a))]
-> ReadPrec (VkSampleCountBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_SAMPLE_COUNT_1_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_1_BIT),
                  (String
"VK_SAMPLE_COUNT_2_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_2_BIT),
                  (String
"VK_SAMPLE_COUNT_4_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_4_BIT),
                  (String
"VK_SAMPLE_COUNT_8_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_8_BIT),
                  (String
"VK_SAMPLE_COUNT_16_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_16_BIT),
                  (String
"VK_SAMPLE_COUNT_32_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_32_BIT),
                  (String
"VK_SAMPLE_COUNT_64_BIT", VkSampleCountBitmask a -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkSampleCountBitmask a
forall (a :: FlagType). VkSampleCountBitmask a
VK_SAMPLE_COUNT_64_BIT)]
                 ReadPrec (VkSampleCountBitmask a)
-> ReadPrec (VkSampleCountBitmask a)
-> ReadPrec (VkSampleCountBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkSampleCountBitmask a)
-> ReadPrec (VkSampleCountBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkSampleCountBitmask") ReadPrec ()
-> ReadPrec (VkSampleCountBitmask a)
-> ReadPrec (VkSampleCountBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkSampleCountBitmask a
forall (a :: FlagType). VkFlags -> VkSampleCountBitmask a
VkSampleCountBitmask (VkFlags -> VkSampleCountBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkSampleCountBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | Sample count 1 supported
--
--   bitpos = @0@
pattern VK_SAMPLE_COUNT_1_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_1_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_1_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_1_BIT = VkSampleCountBitmask 1

-- | Sample count 2 supported
--
--   bitpos = @1@
pattern VK_SAMPLE_COUNT_2_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_2_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_2_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_2_BIT = VkSampleCountBitmask 2

-- | Sample count 4 supported
--
--   bitpos = @2@
pattern VK_SAMPLE_COUNT_4_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_4_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_4_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_4_BIT = VkSampleCountBitmask 4

-- | Sample count 8 supported
--
--   bitpos = @3@
pattern VK_SAMPLE_COUNT_8_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_8_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_8_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_8_BIT = VkSampleCountBitmask 8

-- | Sample count 16 supported
--
--   bitpos = @4@
pattern VK_SAMPLE_COUNT_16_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_16_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_16_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_16_BIT = VkSampleCountBitmask 16

-- | Sample count 32 supported
--
--   bitpos = @5@
pattern VK_SAMPLE_COUNT_32_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_32_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_32_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_32_BIT = VkSampleCountBitmask 32

-- | Sample count 64 supported
--
--   bitpos = @6@
pattern VK_SAMPLE_COUNT_64_BIT :: VkSampleCountBitmask a

pattern $bVK_SAMPLE_COUNT_64_BIT :: VkSampleCountBitmask a
$mVK_SAMPLE_COUNT_64_BIT :: forall r (a :: FlagType).
VkSampleCountBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_SAMPLE_COUNT_64_BIT = VkSampleCountBitmask 64