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

type VkDependencyFlags = VkDependencyBitmask FlagMask

type VkDependencyFlagBits = VkDependencyBitmask FlagBit

pattern VkDependencyFlagBits ::
        VkFlags -> VkDependencyBitmask FlagBit

pattern $bVkDependencyFlagBits :: VkFlags -> VkDependencyBitmask FlagBit
$mVkDependencyFlagBits :: forall r.
VkDependencyBitmask FlagBit -> (VkFlags -> r) -> (Void# -> r) -> r
VkDependencyFlagBits n = VkDependencyBitmask n

pattern VkDependencyFlags ::
        VkFlags -> VkDependencyBitmask FlagMask

pattern $bVkDependencyFlags :: VkFlags -> VkDependencyBitmask FlagMask
$mVkDependencyFlags :: forall r.
VkDependencyBitmask FlagMask -> (VkFlags -> r) -> (Void# -> r) -> r
VkDependencyFlags n = VkDependencyBitmask n

deriving instance Bits (VkDependencyBitmask FlagMask)

deriving instance FiniteBits (VkDependencyBitmask FlagMask)

deriving instance Integral (VkDependencyBitmask FlagMask)

deriving instance Num (VkDependencyBitmask FlagMask)

deriving instance Bounded (VkDependencyBitmask FlagMask)

deriving instance Enum (VkDependencyBitmask FlagMask)

deriving instance Real (VkDependencyBitmask FlagMask)

instance Show (VkDependencyBitmask a) where
        showsPrec :: Int -> VkDependencyBitmask a -> ShowS
showsPrec Int
_ VkDependencyBitmask a
VK_DEPENDENCY_BY_REGION_BIT
          = String -> ShowS
showString String
"VK_DEPENDENCY_BY_REGION_BIT"
        showsPrec Int
p (VkDependencyBitmask VkFlags
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkDependencyBitmask " 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 (VkDependencyBitmask a) where
        readPrec :: ReadPrec (VkDependencyBitmask a)
readPrec
          = ReadPrec (VkDependencyBitmask a)
-> ReadPrec (VkDependencyBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec (VkDependencyBitmask a))]
-> ReadPrec (VkDependencyBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_DEPENDENCY_BY_REGION_BIT", VkDependencyBitmask a -> ReadPrec (VkDependencyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkDependencyBitmask a
forall (a :: FlagType). VkDependencyBitmask a
VK_DEPENDENCY_BY_REGION_BIT)]
                 ReadPrec (VkDependencyBitmask a)
-> ReadPrec (VkDependencyBitmask a)
-> ReadPrec (VkDependencyBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int
-> ReadPrec (VkDependencyBitmask a)
-> ReadPrec (VkDependencyBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkDependencyBitmask") ReadPrec ()
-> ReadPrec (VkDependencyBitmask a)
-> ReadPrec (VkDependencyBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (VkFlags -> VkDependencyBitmask a
forall (a :: FlagType). VkFlags -> VkDependencyBitmask a
VkDependencyBitmask (VkFlags -> VkDependencyBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkDependencyBitmask 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)))

-- | Dependency is per pixel region
--
--   bitpos = @0@
pattern VK_DEPENDENCY_BY_REGION_BIT :: VkDependencyBitmask a

pattern $bVK_DEPENDENCY_BY_REGION_BIT :: VkDependencyBitmask a
$mVK_DEPENDENCY_BY_REGION_BIT :: forall r (a :: FlagType).
VkDependencyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_DEPENDENCY_BY_REGION_BIT = VkDependencyBitmask 1