{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE Strict                     #-}
module Graphics.Vulkan.Types.Enum.ChromaLocation
       (VkChromaLocation(VkChromaLocation,
                         VK_CHROMA_LOCATION_COSITED_EVEN, VK_CHROMA_LOCATION_MIDPOINT),
        VkChromaLocationKHR(..))
       where
import           Data.Bits                       (Bits, FiniteBits)
import           Data.Coerce                     (coerce)
import           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
import           GHC.Read                        (choose, expectP)
import           Graphics.Vulkan.Marshal         (Int32)
import           Graphics.Vulkan.Types.BaseTypes (VkFlags)
import           Text.ParserCombinators.ReadPrec (prec, step, (+++))
import           Text.Read                       (Read (..), parens)
import           Text.Read.Lex                   (Lexeme (..))

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkChromaLocation VkChromaLocation registry at www.khronos.org>
newtype VkChromaLocation = VkChromaLocation Int32
                             deriving (VkChromaLocation -> VkChromaLocation -> Bool
(VkChromaLocation -> VkChromaLocation -> Bool)
-> (VkChromaLocation -> VkChromaLocation -> Bool)
-> Eq VkChromaLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkChromaLocation -> VkChromaLocation -> Bool
$c/= :: VkChromaLocation -> VkChromaLocation -> Bool
== :: VkChromaLocation -> VkChromaLocation -> Bool
$c== :: VkChromaLocation -> VkChromaLocation -> Bool
Eq, Eq VkChromaLocation
Eq VkChromaLocation
-> (VkChromaLocation -> VkChromaLocation -> Ordering)
-> (VkChromaLocation -> VkChromaLocation -> Bool)
-> (VkChromaLocation -> VkChromaLocation -> Bool)
-> (VkChromaLocation -> VkChromaLocation -> Bool)
-> (VkChromaLocation -> VkChromaLocation -> Bool)
-> (VkChromaLocation -> VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation -> VkChromaLocation)
-> Ord VkChromaLocation
VkChromaLocation -> VkChromaLocation -> Bool
VkChromaLocation -> VkChromaLocation -> Ordering
VkChromaLocation -> VkChromaLocation -> VkChromaLocation
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 :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
$cmin :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
max :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
$cmax :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
>= :: VkChromaLocation -> VkChromaLocation -> Bool
$c>= :: VkChromaLocation -> VkChromaLocation -> Bool
> :: VkChromaLocation -> VkChromaLocation -> Bool
$c> :: VkChromaLocation -> VkChromaLocation -> Bool
<= :: VkChromaLocation -> VkChromaLocation -> Bool
$c<= :: VkChromaLocation -> VkChromaLocation -> Bool
< :: VkChromaLocation -> VkChromaLocation -> Bool
$c< :: VkChromaLocation -> VkChromaLocation -> Bool
compare :: VkChromaLocation -> VkChromaLocation -> Ordering
$ccompare :: VkChromaLocation -> VkChromaLocation -> Ordering
$cp1Ord :: Eq VkChromaLocation
Ord, Integer -> VkChromaLocation
VkChromaLocation -> VkChromaLocation
VkChromaLocation -> VkChromaLocation -> VkChromaLocation
(VkChromaLocation -> VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation)
-> (Integer -> VkChromaLocation)
-> Num VkChromaLocation
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkChromaLocation
$cfromInteger :: Integer -> VkChromaLocation
signum :: VkChromaLocation -> VkChromaLocation
$csignum :: VkChromaLocation -> VkChromaLocation
abs :: VkChromaLocation -> VkChromaLocation
$cabs :: VkChromaLocation -> VkChromaLocation
negate :: VkChromaLocation -> VkChromaLocation
$cnegate :: VkChromaLocation -> VkChromaLocation
* :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
$c* :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
- :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
$c- :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
+ :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
$c+ :: VkChromaLocation -> VkChromaLocation -> VkChromaLocation
Num, VkChromaLocation
VkChromaLocation -> VkChromaLocation -> Bounded VkChromaLocation
forall a. a -> a -> Bounded a
maxBound :: VkChromaLocation
$cmaxBound :: VkChromaLocation
minBound :: VkChromaLocation
$cminBound :: VkChromaLocation
Bounded, Ptr b -> Int -> IO VkChromaLocation
Ptr b -> Int -> VkChromaLocation -> IO ()
Ptr VkChromaLocation -> IO VkChromaLocation
Ptr VkChromaLocation -> Int -> IO VkChromaLocation
Ptr VkChromaLocation -> Int -> VkChromaLocation -> IO ()
Ptr VkChromaLocation -> VkChromaLocation -> IO ()
VkChromaLocation -> Int
(VkChromaLocation -> Int)
-> (VkChromaLocation -> Int)
-> (Ptr VkChromaLocation -> Int -> IO VkChromaLocation)
-> (Ptr VkChromaLocation -> Int -> VkChromaLocation -> IO ())
-> (forall b. Ptr b -> Int -> IO VkChromaLocation)
-> (forall b. Ptr b -> Int -> VkChromaLocation -> IO ())
-> (Ptr VkChromaLocation -> IO VkChromaLocation)
-> (Ptr VkChromaLocation -> VkChromaLocation -> IO ())
-> Storable VkChromaLocation
forall b. Ptr b -> Int -> IO VkChromaLocation
forall b. Ptr b -> Int -> VkChromaLocation -> 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 VkChromaLocation -> VkChromaLocation -> IO ()
$cpoke :: Ptr VkChromaLocation -> VkChromaLocation -> IO ()
peek :: Ptr VkChromaLocation -> IO VkChromaLocation
$cpeek :: Ptr VkChromaLocation -> IO VkChromaLocation
pokeByteOff :: Ptr b -> Int -> VkChromaLocation -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkChromaLocation -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkChromaLocation
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkChromaLocation
pokeElemOff :: Ptr VkChromaLocation -> Int -> VkChromaLocation -> IO ()
$cpokeElemOff :: Ptr VkChromaLocation -> Int -> VkChromaLocation -> IO ()
peekElemOff :: Ptr VkChromaLocation -> Int -> IO VkChromaLocation
$cpeekElemOff :: Ptr VkChromaLocation -> Int -> IO VkChromaLocation
alignment :: VkChromaLocation -> Int
$calignment :: VkChromaLocation -> Int
sizeOf :: VkChromaLocation -> Int
$csizeOf :: VkChromaLocation -> Int
Storable, Int -> VkChromaLocation
VkChromaLocation -> Int
VkChromaLocation -> [VkChromaLocation]
VkChromaLocation -> VkChromaLocation
VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
VkChromaLocation
-> VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
(VkChromaLocation -> VkChromaLocation)
-> (VkChromaLocation -> VkChromaLocation)
-> (Int -> VkChromaLocation)
-> (VkChromaLocation -> Int)
-> (VkChromaLocation -> [VkChromaLocation])
-> (VkChromaLocation -> VkChromaLocation -> [VkChromaLocation])
-> (VkChromaLocation -> VkChromaLocation -> [VkChromaLocation])
-> (VkChromaLocation
    -> VkChromaLocation -> VkChromaLocation -> [VkChromaLocation])
-> Enum VkChromaLocation
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkChromaLocation
-> VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
$cenumFromThenTo :: VkChromaLocation
-> VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
enumFromTo :: VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
$cenumFromTo :: VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
enumFromThen :: VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
$cenumFromThen :: VkChromaLocation -> VkChromaLocation -> [VkChromaLocation]
enumFrom :: VkChromaLocation -> [VkChromaLocation]
$cenumFrom :: VkChromaLocation -> [VkChromaLocation]
fromEnum :: VkChromaLocation -> Int
$cfromEnum :: VkChromaLocation -> Int
toEnum :: Int -> VkChromaLocation
$ctoEnum :: Int -> VkChromaLocation
pred :: VkChromaLocation -> VkChromaLocation
$cpred :: VkChromaLocation -> VkChromaLocation
succ :: VkChromaLocation -> VkChromaLocation
$csucc :: VkChromaLocation -> VkChromaLocation
Enum, Typeable VkChromaLocation
DataType
Constr
Typeable VkChromaLocation
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkChromaLocation)
-> (VkChromaLocation -> Constr)
-> (VkChromaLocation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkChromaLocation))
-> ((forall b. Data b => b -> b)
    -> VkChromaLocation -> VkChromaLocation)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkChromaLocation -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkChromaLocation -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocation -> m VkChromaLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocation -> m VkChromaLocation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocation -> m VkChromaLocation)
-> Data VkChromaLocation
VkChromaLocation -> DataType
VkChromaLocation -> Constr
(forall b. Data b => b -> b)
-> VkChromaLocation -> VkChromaLocation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocation
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) -> VkChromaLocation -> u
forall u. (forall d. Data d => d -> u) -> VkChromaLocation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkChromaLocation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocation)
$cVkChromaLocation :: Constr
$tVkChromaLocation :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
gmapMp :: (forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
gmapM :: (forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkChromaLocation -> m VkChromaLocation
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkChromaLocation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> VkChromaLocation -> u
gmapQ :: (forall d. Data d => d -> u) -> VkChromaLocation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VkChromaLocation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocation -> r
gmapT :: (forall b. Data b => b -> b)
-> VkChromaLocation -> VkChromaLocation
$cgmapT :: (forall b. Data b => b -> b)
-> VkChromaLocation -> VkChromaLocation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkChromaLocation)
dataTypeOf :: VkChromaLocation -> DataType
$cdataTypeOf :: VkChromaLocation -> DataType
toConstr :: VkChromaLocation -> Constr
$ctoConstr :: VkChromaLocation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VkChromaLocation -> c VkChromaLocation
$cp1Data :: Typeable VkChromaLocation
Data, (forall x. VkChromaLocation -> Rep VkChromaLocation x)
-> (forall x. Rep VkChromaLocation x -> VkChromaLocation)
-> Generic VkChromaLocation
forall x. Rep VkChromaLocation x -> VkChromaLocation
forall x. VkChromaLocation -> Rep VkChromaLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VkChromaLocation x -> VkChromaLocation
$cfrom :: forall x. VkChromaLocation -> Rep VkChromaLocation x
Generic)

instance Show VkChromaLocation where
        showsPrec :: Int -> VkChromaLocation -> ShowS
showsPrec Int
_ VkChromaLocation
VK_CHROMA_LOCATION_COSITED_EVEN
          = String -> ShowS
showString String
"VK_CHROMA_LOCATION_COSITED_EVEN"
        showsPrec Int
_ VkChromaLocation
VK_CHROMA_LOCATION_MIDPOINT
          = String -> ShowS
showString String
"VK_CHROMA_LOCATION_MIDPOINT"
        showsPrec Int
p (VkChromaLocation Int32
x)
          = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
              (String -> ShowS
showString String
"VkChromaLocation " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkChromaLocation where
        readPrec :: ReadPrec VkChromaLocation
readPrec
          = ReadPrec VkChromaLocation -> ReadPrec VkChromaLocation
forall a. ReadPrec a -> ReadPrec a
parens
              ([(String, ReadPrec VkChromaLocation)] -> ReadPrec VkChromaLocation
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
                 [(String
"VK_CHROMA_LOCATION_COSITED_EVEN",
                   VkChromaLocation -> ReadPrec VkChromaLocation
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkChromaLocation
VK_CHROMA_LOCATION_COSITED_EVEN),
                  (String
"VK_CHROMA_LOCATION_MIDPOINT", VkChromaLocation -> ReadPrec VkChromaLocation
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkChromaLocation
VK_CHROMA_LOCATION_MIDPOINT)]
                 ReadPrec VkChromaLocation
-> ReadPrec VkChromaLocation -> ReadPrec VkChromaLocation
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                 Int -> ReadPrec VkChromaLocation -> ReadPrec VkChromaLocation
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
                   (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkChromaLocation") ReadPrec ()
-> ReadPrec VkChromaLocation -> ReadPrec VkChromaLocation
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                      (Int32 -> VkChromaLocation
VkChromaLocation (Int32 -> VkChromaLocation)
-> ReadPrec Int32 -> ReadPrec VkChromaLocation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_CHROMA_LOCATION_COSITED_EVEN :: VkChromaLocation

pattern $bVK_CHROMA_LOCATION_COSITED_EVEN :: VkChromaLocation
$mVK_CHROMA_LOCATION_COSITED_EVEN :: forall r. VkChromaLocation -> (Void# -> r) -> (Void# -> r) -> r
VK_CHROMA_LOCATION_COSITED_EVEN = VkChromaLocation 0

pattern VK_CHROMA_LOCATION_MIDPOINT :: VkChromaLocation

pattern $bVK_CHROMA_LOCATION_MIDPOINT :: VkChromaLocation
$mVK_CHROMA_LOCATION_MIDPOINT :: forall r. VkChromaLocation -> (Void# -> r) -> (Void# -> r) -> r
VK_CHROMA_LOCATION_MIDPOINT = VkChromaLocation 1

newtype VkChromaLocationKHR = VkChromaLocationKHR VkFlags
                                deriving (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
(VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> Eq VkChromaLocationKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c/= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
== :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c== :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
Eq, Eq VkChromaLocationKHR
Eq VkChromaLocationKHR
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Ordering)
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR -> VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> Ord VkChromaLocationKHR
VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
VkChromaLocationKHR -> VkChromaLocationKHR -> Ordering
VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
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 :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cmin :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
max :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cmax :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
>= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c>= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
> :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c> :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
<= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c<= :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
< :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
$c< :: VkChromaLocationKHR -> VkChromaLocationKHR -> Bool
compare :: VkChromaLocationKHR -> VkChromaLocationKHR -> Ordering
$ccompare :: VkChromaLocationKHR -> VkChromaLocationKHR -> Ordering
$cp1Ord :: Eq VkChromaLocationKHR
Ord, Integer -> VkChromaLocationKHR
VkChromaLocationKHR -> VkChromaLocationKHR
VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
(VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> VkChromaLocationKHR)
-> (Integer -> VkChromaLocationKHR)
-> Num VkChromaLocationKHR
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkChromaLocationKHR
$cfromInteger :: Integer -> VkChromaLocationKHR
signum :: VkChromaLocationKHR -> VkChromaLocationKHR
$csignum :: VkChromaLocationKHR -> VkChromaLocationKHR
abs :: VkChromaLocationKHR -> VkChromaLocationKHR
$cabs :: VkChromaLocationKHR -> VkChromaLocationKHR
negate :: VkChromaLocationKHR -> VkChromaLocationKHR
$cnegate :: VkChromaLocationKHR -> VkChromaLocationKHR
* :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$c* :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
- :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$c- :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
+ :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$c+ :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
Num, VkChromaLocationKHR
VkChromaLocationKHR
-> VkChromaLocationKHR -> Bounded VkChromaLocationKHR
forall a. a -> a -> Bounded a
maxBound :: VkChromaLocationKHR
$cmaxBound :: VkChromaLocationKHR
minBound :: VkChromaLocationKHR
$cminBound :: VkChromaLocationKHR
Bounded, Int -> VkChromaLocationKHR
VkChromaLocationKHR -> Int
VkChromaLocationKHR -> [VkChromaLocationKHR]
VkChromaLocationKHR -> VkChromaLocationKHR
VkChromaLocationKHR -> VkChromaLocationKHR -> [VkChromaLocationKHR]
VkChromaLocationKHR
-> VkChromaLocationKHR
-> VkChromaLocationKHR
-> [VkChromaLocationKHR]
(VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> VkChromaLocationKHR)
-> (Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int)
-> (VkChromaLocationKHR -> [VkChromaLocationKHR])
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> [VkChromaLocationKHR])
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> [VkChromaLocationKHR])
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR
    -> VkChromaLocationKHR
    -> [VkChromaLocationKHR])
-> Enum VkChromaLocationKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> VkChromaLocationKHR
-> [VkChromaLocationKHR]
$cenumFromThenTo :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> VkChromaLocationKHR
-> [VkChromaLocationKHR]
enumFromTo :: VkChromaLocationKHR -> VkChromaLocationKHR -> [VkChromaLocationKHR]
$cenumFromTo :: VkChromaLocationKHR -> VkChromaLocationKHR -> [VkChromaLocationKHR]
enumFromThen :: VkChromaLocationKHR -> VkChromaLocationKHR -> [VkChromaLocationKHR]
$cenumFromThen :: VkChromaLocationKHR -> VkChromaLocationKHR -> [VkChromaLocationKHR]
enumFrom :: VkChromaLocationKHR -> [VkChromaLocationKHR]
$cenumFrom :: VkChromaLocationKHR -> [VkChromaLocationKHR]
fromEnum :: VkChromaLocationKHR -> Int
$cfromEnum :: VkChromaLocationKHR -> Int
toEnum :: Int -> VkChromaLocationKHR
$ctoEnum :: Int -> VkChromaLocationKHR
pred :: VkChromaLocationKHR -> VkChromaLocationKHR
$cpred :: VkChromaLocationKHR -> VkChromaLocationKHR
succ :: VkChromaLocationKHR -> VkChromaLocationKHR
$csucc :: VkChromaLocationKHR -> VkChromaLocationKHR
Enum, Enum VkChromaLocationKHR
Real VkChromaLocationKHR
Real VkChromaLocationKHR
-> Enum VkChromaLocationKHR
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR
    -> (VkChromaLocationKHR, VkChromaLocationKHR))
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR
    -> (VkChromaLocationKHR, VkChromaLocationKHR))
-> (VkChromaLocationKHR -> Integer)
-> Integral VkChromaLocationKHR
VkChromaLocationKHR -> Integer
VkChromaLocationKHR
-> VkChromaLocationKHR
-> (VkChromaLocationKHR, VkChromaLocationKHR)
VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: VkChromaLocationKHR -> Integer
$ctoInteger :: VkChromaLocationKHR -> Integer
divMod :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> (VkChromaLocationKHR, VkChromaLocationKHR)
$cdivMod :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> (VkChromaLocationKHR, VkChromaLocationKHR)
quotRem :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> (VkChromaLocationKHR, VkChromaLocationKHR)
$cquotRem :: VkChromaLocationKHR
-> VkChromaLocationKHR
-> (VkChromaLocationKHR, VkChromaLocationKHR)
mod :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cmod :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
div :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cdiv :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
rem :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$crem :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
quot :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cquot :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cp2Integral :: Enum VkChromaLocationKHR
$cp1Integral :: Real VkChromaLocationKHR
Integral, Eq VkChromaLocationKHR
VkChromaLocationKHR
Eq VkChromaLocationKHR
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> VkChromaLocationKHR
-> (Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> Bool)
-> (VkChromaLocationKHR -> Maybe Int)
-> (VkChromaLocationKHR -> Int)
-> (VkChromaLocationKHR -> Bool)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int -> VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Int)
-> Bits VkChromaLocationKHR
Int -> VkChromaLocationKHR
VkChromaLocationKHR -> Bool
VkChromaLocationKHR -> Int
VkChromaLocationKHR -> Maybe Int
VkChromaLocationKHR -> VkChromaLocationKHR
VkChromaLocationKHR -> Int -> Bool
VkChromaLocationKHR -> Int -> VkChromaLocationKHR
VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
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 :: VkChromaLocationKHR -> Int
$cpopCount :: VkChromaLocationKHR -> Int
rotateR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$crotateR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
rotateL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$crotateL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
unsafeShiftR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cunsafeShiftR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
shiftR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cshiftR :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
unsafeShiftL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cunsafeShiftL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
shiftL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cshiftL :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
isSigned :: VkChromaLocationKHR -> Bool
$cisSigned :: VkChromaLocationKHR -> Bool
bitSize :: VkChromaLocationKHR -> Int
$cbitSize :: VkChromaLocationKHR -> Int
bitSizeMaybe :: VkChromaLocationKHR -> Maybe Int
$cbitSizeMaybe :: VkChromaLocationKHR -> Maybe Int
testBit :: VkChromaLocationKHR -> Int -> Bool
$ctestBit :: VkChromaLocationKHR -> Int -> Bool
complementBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$ccomplementBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
clearBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cclearBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
setBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$csetBit :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
bit :: Int -> VkChromaLocationKHR
$cbit :: Int -> VkChromaLocationKHR
zeroBits :: VkChromaLocationKHR
$czeroBits :: VkChromaLocationKHR
rotate :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$crotate :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
shift :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
$cshift :: VkChromaLocationKHR -> Int -> VkChromaLocationKHR
complement :: VkChromaLocationKHR -> VkChromaLocationKHR
$ccomplement :: VkChromaLocationKHR -> VkChromaLocationKHR
xor :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cxor :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
.|. :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$c.|. :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
.&. :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$c.&. :: VkChromaLocationKHR -> VkChromaLocationKHR -> VkChromaLocationKHR
$cp1Bits :: Eq VkChromaLocationKHR
Bits, Bits VkChromaLocationKHR
Bits VkChromaLocationKHR
-> (VkChromaLocationKHR -> Int)
-> (VkChromaLocationKHR -> Int)
-> (VkChromaLocationKHR -> Int)
-> FiniteBits VkChromaLocationKHR
VkChromaLocationKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkChromaLocationKHR -> Int
$ccountTrailingZeros :: VkChromaLocationKHR -> Int
countLeadingZeros :: VkChromaLocationKHR -> Int
$ccountLeadingZeros :: VkChromaLocationKHR -> Int
finiteBitSize :: VkChromaLocationKHR -> Int
$cfiniteBitSize :: VkChromaLocationKHR -> Int
$cp1FiniteBits :: Bits VkChromaLocationKHR
FiniteBits,
                                          Ptr b -> Int -> IO VkChromaLocationKHR
Ptr b -> Int -> VkChromaLocationKHR -> IO ()
Ptr VkChromaLocationKHR -> IO VkChromaLocationKHR
Ptr VkChromaLocationKHR -> Int -> IO VkChromaLocationKHR
Ptr VkChromaLocationKHR -> Int -> VkChromaLocationKHR -> IO ()
Ptr VkChromaLocationKHR -> VkChromaLocationKHR -> IO ()
VkChromaLocationKHR -> Int
(VkChromaLocationKHR -> Int)
-> (VkChromaLocationKHR -> Int)
-> (Ptr VkChromaLocationKHR -> Int -> IO VkChromaLocationKHR)
-> (Ptr VkChromaLocationKHR -> Int -> VkChromaLocationKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkChromaLocationKHR)
-> (forall b. Ptr b -> Int -> VkChromaLocationKHR -> IO ())
-> (Ptr VkChromaLocationKHR -> IO VkChromaLocationKHR)
-> (Ptr VkChromaLocationKHR -> VkChromaLocationKHR -> IO ())
-> Storable VkChromaLocationKHR
forall b. Ptr b -> Int -> IO VkChromaLocationKHR
forall b. Ptr b -> Int -> VkChromaLocationKHR -> 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 VkChromaLocationKHR -> VkChromaLocationKHR -> IO ()
$cpoke :: Ptr VkChromaLocationKHR -> VkChromaLocationKHR -> IO ()
peek :: Ptr VkChromaLocationKHR -> IO VkChromaLocationKHR
$cpeek :: Ptr VkChromaLocationKHR -> IO VkChromaLocationKHR
pokeByteOff :: Ptr b -> Int -> VkChromaLocationKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkChromaLocationKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO VkChromaLocationKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkChromaLocationKHR
pokeElemOff :: Ptr VkChromaLocationKHR -> Int -> VkChromaLocationKHR -> IO ()
$cpokeElemOff :: Ptr VkChromaLocationKHR -> Int -> VkChromaLocationKHR -> IO ()
peekElemOff :: Ptr VkChromaLocationKHR -> Int -> IO VkChromaLocationKHR
$cpeekElemOff :: Ptr VkChromaLocationKHR -> Int -> IO VkChromaLocationKHR
alignment :: VkChromaLocationKHR -> Int
$calignment :: VkChromaLocationKHR -> Int
sizeOf :: VkChromaLocationKHR -> Int
$csizeOf :: VkChromaLocationKHR -> Int
Storable, Num VkChromaLocationKHR
Ord VkChromaLocationKHR
Num VkChromaLocationKHR
-> Ord VkChromaLocationKHR
-> (VkChromaLocationKHR -> Rational)
-> Real VkChromaLocationKHR
VkChromaLocationKHR -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: VkChromaLocationKHR -> Rational
$ctoRational :: VkChromaLocationKHR -> Rational
$cp2Real :: Ord VkChromaLocationKHR
$cp1Real :: Num VkChromaLocationKHR
Real, Typeable VkChromaLocationKHR
DataType
Constr
Typeable VkChromaLocationKHR
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkChromaLocationKHR
    -> c VkChromaLocationKHR)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR)
-> (VkChromaLocationKHR -> Constr)
-> (VkChromaLocationKHR -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocationKHR))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkChromaLocationKHR))
-> ((forall b. Data b => b -> b)
    -> VkChromaLocationKHR -> VkChromaLocationKHR)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkChromaLocationKHR -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkChromaLocationKHR -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocationKHR -> m VkChromaLocationKHR)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocationKHR -> m VkChromaLocationKHR)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkChromaLocationKHR -> m VkChromaLocationKHR)
-> Data VkChromaLocationKHR
VkChromaLocationKHR -> DataType
VkChromaLocationKHR -> Constr
(forall b. Data b => b -> b)
-> VkChromaLocationKHR -> VkChromaLocationKHR
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkChromaLocationKHR
-> c VkChromaLocationKHR
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR
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) -> VkChromaLocationKHR -> u
forall u.
(forall d. Data d => d -> u) -> VkChromaLocationKHR -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkChromaLocationKHR
-> c VkChromaLocationKHR
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkChromaLocationKHR)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocationKHR)
$cVkChromaLocationKHR :: Constr
$tVkChromaLocationKHR :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
gmapMp :: (forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
gmapM :: (forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkChromaLocationKHR -> m VkChromaLocationKHR
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkChromaLocationKHR -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> VkChromaLocationKHR -> u
gmapQ :: (forall d. Data d => d -> u) -> VkChromaLocationKHR -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> VkChromaLocationKHR -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkChromaLocationKHR -> r
gmapT :: (forall b. Data b => b -> b)
-> VkChromaLocationKHR -> VkChromaLocationKHR
$cgmapT :: (forall b. Data b => b -> b)
-> VkChromaLocationKHR -> VkChromaLocationKHR
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocationKHR)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkChromaLocationKHR)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VkChromaLocationKHR)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VkChromaLocationKHR)
dataTypeOf :: VkChromaLocationKHR -> DataType
$cdataTypeOf :: VkChromaLocationKHR -> DataType
toConstr :: VkChromaLocationKHR -> Constr
$ctoConstr :: VkChromaLocationKHR -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkChromaLocationKHR
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkChromaLocationKHR
-> c VkChromaLocationKHR
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkChromaLocationKHR
-> c VkChromaLocationKHR
$cp1Data :: Typeable VkChromaLocationKHR
Data, (forall x. VkChromaLocationKHR -> Rep VkChromaLocationKHR x)
-> (forall x. Rep VkChromaLocationKHR x -> VkChromaLocationKHR)
-> Generic VkChromaLocationKHR
forall x. Rep VkChromaLocationKHR x -> VkChromaLocationKHR
forall x. VkChromaLocationKHR -> Rep VkChromaLocationKHR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VkChromaLocationKHR x -> VkChromaLocationKHR
$cfrom :: forall x. VkChromaLocationKHR -> Rep VkChromaLocationKHR x
Generic)

instance Show VkChromaLocationKHR where
        {-# INLINE show #-}
        show :: VkChromaLocationKHR -> String
show (VkChromaLocationKHR VkFlags
x) = VkFlags -> String
forall a. Show a => a -> String
show VkFlags
x

instance Read VkChromaLocationKHR where
        {-# INLINE readsPrec #-}
        readsPrec :: Int -> ReadS VkChromaLocationKHR
readsPrec = (Int -> ReadS VkFlags) -> Int -> ReadS VkChromaLocationKHR
coerce (Int -> ReadS VkFlags
forall a. Read a => Int -> ReadS a
readsPrec :: Int -> ReadS VkFlags)