{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Graphics.Vulkan.Types.Enum.Attachment
(VkAttachmentDescriptionBitmask(VkAttachmentDescriptionBitmask,
VkAttachmentDescriptionFlags,
VkAttachmentDescriptionFlagBits,
VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT),
VkAttachmentDescriptionFlags, VkAttachmentDescriptionFlagBits,
VkAttachmentLoadOp(VkAttachmentLoadOp, VK_ATTACHMENT_LOAD_OP_LOAD,
VK_ATTACHMENT_LOAD_OP_CLEAR, VK_ATTACHMENT_LOAD_OP_DONT_CARE),
VkAttachmentStoreOp(VkAttachmentStoreOp,
VK_ATTACHMENT_STORE_OP_STORE, VK_ATTACHMENT_STORE_OP_DONT_CARE))
where
import Data.Bits (Bits, FiniteBits)
import Foreign.Storable (Storable)
import GHC.Read (choose, expectP)
import Graphics.Vulkan.Marshal (FlagBit, FlagMask, FlagType, Int32)
import Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import Text.ParserCombinators.ReadPrec (prec, step, (+++))
import Text.Read (Read (..), parens)
import Text.Read.Lex (Lexeme (..))
newtype VkAttachmentDescriptionBitmask (a ::
FlagType) = VkAttachmentDescriptionBitmask VkFlags
deriving (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
(VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> Eq (VkAttachmentDescriptionBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
/= :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
== :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
Eq, Eq (VkAttachmentDescriptionBitmask a)
Eq (VkAttachmentDescriptionBitmask a)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Ordering)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a)
-> (VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a)
-> Ord (VkAttachmentDescriptionBitmask a)
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Ordering
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask 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 (VkAttachmentDescriptionBitmask a)
forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Ordering
forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
min :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
$cmin :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
max :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
$cmax :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a
>= :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
> :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
<= :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
< :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Bool
compare :: VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkAttachmentDescriptionBitmask a
-> VkAttachmentDescriptionBitmask a -> Ordering
Ord, Ptr (VkAttachmentDescriptionBitmask a)
-> IO (VkAttachmentDescriptionBitmask a)
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> IO (VkAttachmentDescriptionBitmask a)
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> VkAttachmentDescriptionBitmask a -> IO ()
Ptr (VkAttachmentDescriptionBitmask a)
-> VkAttachmentDescriptionBitmask a -> IO ()
VkAttachmentDescriptionBitmask a -> Int
(VkAttachmentDescriptionBitmask a -> Int)
-> (VkAttachmentDescriptionBitmask a -> Int)
-> (Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> IO (VkAttachmentDescriptionBitmask a))
-> (Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> VkAttachmentDescriptionBitmask a -> IO ())
-> (forall b.
Ptr b -> Int -> IO (VkAttachmentDescriptionBitmask a))
-> (forall b.
Ptr b -> Int -> VkAttachmentDescriptionBitmask a -> IO ())
-> (Ptr (VkAttachmentDescriptionBitmask a)
-> IO (VkAttachmentDescriptionBitmask a))
-> (Ptr (VkAttachmentDescriptionBitmask a)
-> VkAttachmentDescriptionBitmask a -> IO ())
-> Storable (VkAttachmentDescriptionBitmask a)
forall b. Ptr b -> Int -> IO (VkAttachmentDescriptionBitmask a)
forall b. Ptr b -> Int -> VkAttachmentDescriptionBitmask 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 (VkAttachmentDescriptionBitmask a)
-> IO (VkAttachmentDescriptionBitmask a)
forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> IO (VkAttachmentDescriptionBitmask a)
forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> VkAttachmentDescriptionBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> VkAttachmentDescriptionBitmask a -> IO ()
forall (a :: FlagType). VkAttachmentDescriptionBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkAttachmentDescriptionBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkAttachmentDescriptionBitmask a -> IO ()
poke :: Ptr (VkAttachmentDescriptionBitmask a)
-> VkAttachmentDescriptionBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> VkAttachmentDescriptionBitmask a -> IO ()
peek :: Ptr (VkAttachmentDescriptionBitmask a)
-> IO (VkAttachmentDescriptionBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> IO (VkAttachmentDescriptionBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkAttachmentDescriptionBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkAttachmentDescriptionBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkAttachmentDescriptionBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkAttachmentDescriptionBitmask a)
pokeElemOff :: Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> VkAttachmentDescriptionBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> VkAttachmentDescriptionBitmask a -> IO ()
peekElemOff :: Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> IO (VkAttachmentDescriptionBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkAttachmentDescriptionBitmask a)
-> Int -> IO (VkAttachmentDescriptionBitmask a)
alignment :: VkAttachmentDescriptionBitmask a -> Int
$calignment :: forall (a :: FlagType). VkAttachmentDescriptionBitmask a -> Int
sizeOf :: VkAttachmentDescriptionBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkAttachmentDescriptionBitmask a -> Int
Storable)
type VkAttachmentDescriptionFlags =
VkAttachmentDescriptionBitmask FlagMask
type VkAttachmentDescriptionFlagBits =
VkAttachmentDescriptionBitmask FlagBit
pattern VkAttachmentDescriptionFlagBits ::
VkFlags -> VkAttachmentDescriptionBitmask FlagBit
pattern $bVkAttachmentDescriptionFlagBits :: VkFlags -> VkAttachmentDescriptionBitmask FlagBit
$mVkAttachmentDescriptionFlagBits :: forall {r}.
VkAttachmentDescriptionBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkAttachmentDescriptionFlagBits n =
VkAttachmentDescriptionBitmask n
pattern VkAttachmentDescriptionFlags ::
VkFlags -> VkAttachmentDescriptionBitmask FlagMask
pattern $bVkAttachmentDescriptionFlags :: VkFlags -> VkAttachmentDescriptionBitmask FlagMask
$mVkAttachmentDescriptionFlags :: forall {r}.
VkAttachmentDescriptionBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkAttachmentDescriptionFlags n =
VkAttachmentDescriptionBitmask n
deriving instance Bits (VkAttachmentDescriptionBitmask FlagMask)
deriving instance
FiniteBits (VkAttachmentDescriptionBitmask FlagMask)
instance Show (VkAttachmentDescriptionBitmask a) where
showsPrec :: Int -> VkAttachmentDescriptionBitmask a -> ShowS
showsPrec Int
_ VkAttachmentDescriptionBitmask a
VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT
= String -> ShowS
showString String
"VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT"
showsPrec Int
p (VkAttachmentDescriptionBitmask VkFlags
x)
= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
(String -> ShowS
showString String
"VkAttachmentDescriptionBitmask " 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 (VkAttachmentDescriptionBitmask a) where
readPrec :: ReadPrec (VkAttachmentDescriptionBitmask a)
readPrec
= ReadPrec (VkAttachmentDescriptionBitmask a)
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
([(String, ReadPrec (VkAttachmentDescriptionBitmask a))]
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
[(String
"VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT",
VkAttachmentDescriptionBitmask a
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentDescriptionBitmask a
forall (a :: FlagType). VkAttachmentDescriptionBitmask a
VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT)]
ReadPrec (VkAttachmentDescriptionBitmask a)
-> ReadPrec (VkAttachmentDescriptionBitmask a)
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec (VkAttachmentDescriptionBitmask a)
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
(Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkAttachmentDescriptionBitmask") ReadPrec ()
-> ReadPrec (VkAttachmentDescriptionBitmask a)
-> ReadPrec (VkAttachmentDescriptionBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(VkFlags -> VkAttachmentDescriptionBitmask a
forall (a :: FlagType). VkFlags -> VkAttachmentDescriptionBitmask a
VkAttachmentDescriptionBitmask (VkFlags -> VkAttachmentDescriptionBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkAttachmentDescriptionBitmask 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)))
pattern VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT ::
VkAttachmentDescriptionBitmask a
pattern $bVK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT :: forall (a :: FlagType). VkAttachmentDescriptionBitmask a
$mVK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT :: forall {r} {a :: FlagType}.
VkAttachmentDescriptionBitmask a
-> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT =
VkAttachmentDescriptionBitmask 1
newtype VkAttachmentLoadOp = VkAttachmentLoadOp Int32
deriving (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
(VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> Eq VkAttachmentLoadOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c/= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
== :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c== :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
Eq, Eq VkAttachmentLoadOp
Eq VkAttachmentLoadOp
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Ordering)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp)
-> Ord VkAttachmentLoadOp
VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
VkAttachmentLoadOp -> VkAttachmentLoadOp -> Ordering
VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp
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 :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp
$cmin :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp
max :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp
$cmax :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> VkAttachmentLoadOp
>= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c>= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
> :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c> :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
<= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c<= :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
< :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
$c< :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Bool
compare :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Ordering
$ccompare :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> Ordering
Ord, Int -> VkAttachmentLoadOp
VkAttachmentLoadOp -> Int
VkAttachmentLoadOp -> [VkAttachmentLoadOp]
VkAttachmentLoadOp -> VkAttachmentLoadOp
VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
VkAttachmentLoadOp
-> VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
(VkAttachmentLoadOp -> VkAttachmentLoadOp)
-> (VkAttachmentLoadOp -> VkAttachmentLoadOp)
-> (Int -> VkAttachmentLoadOp)
-> (VkAttachmentLoadOp -> Int)
-> (VkAttachmentLoadOp -> [VkAttachmentLoadOp])
-> (VkAttachmentLoadOp
-> VkAttachmentLoadOp -> [VkAttachmentLoadOp])
-> (VkAttachmentLoadOp
-> VkAttachmentLoadOp -> [VkAttachmentLoadOp])
-> (VkAttachmentLoadOp
-> VkAttachmentLoadOp
-> VkAttachmentLoadOp
-> [VkAttachmentLoadOp])
-> Enum VkAttachmentLoadOp
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 :: VkAttachmentLoadOp
-> VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
$cenumFromThenTo :: VkAttachmentLoadOp
-> VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
enumFromTo :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
$cenumFromTo :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
enumFromThen :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
$cenumFromThen :: VkAttachmentLoadOp -> VkAttachmentLoadOp -> [VkAttachmentLoadOp]
enumFrom :: VkAttachmentLoadOp -> [VkAttachmentLoadOp]
$cenumFrom :: VkAttachmentLoadOp -> [VkAttachmentLoadOp]
fromEnum :: VkAttachmentLoadOp -> Int
$cfromEnum :: VkAttachmentLoadOp -> Int
toEnum :: Int -> VkAttachmentLoadOp
$ctoEnum :: Int -> VkAttachmentLoadOp
pred :: VkAttachmentLoadOp -> VkAttachmentLoadOp
$cpred :: VkAttachmentLoadOp -> VkAttachmentLoadOp
succ :: VkAttachmentLoadOp -> VkAttachmentLoadOp
$csucc :: VkAttachmentLoadOp -> VkAttachmentLoadOp
Enum, Ptr VkAttachmentLoadOp -> IO VkAttachmentLoadOp
Ptr VkAttachmentLoadOp -> Int -> IO VkAttachmentLoadOp
Ptr VkAttachmentLoadOp -> Int -> VkAttachmentLoadOp -> IO ()
Ptr VkAttachmentLoadOp -> VkAttachmentLoadOp -> IO ()
VkAttachmentLoadOp -> Int
(VkAttachmentLoadOp -> Int)
-> (VkAttachmentLoadOp -> Int)
-> (Ptr VkAttachmentLoadOp -> Int -> IO VkAttachmentLoadOp)
-> (Ptr VkAttachmentLoadOp -> Int -> VkAttachmentLoadOp -> IO ())
-> (forall b. Ptr b -> Int -> IO VkAttachmentLoadOp)
-> (forall b. Ptr b -> Int -> VkAttachmentLoadOp -> IO ())
-> (Ptr VkAttachmentLoadOp -> IO VkAttachmentLoadOp)
-> (Ptr VkAttachmentLoadOp -> VkAttachmentLoadOp -> IO ())
-> Storable VkAttachmentLoadOp
forall b. Ptr b -> Int -> IO VkAttachmentLoadOp
forall b. Ptr b -> Int -> VkAttachmentLoadOp -> 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 VkAttachmentLoadOp -> VkAttachmentLoadOp -> IO ()
$cpoke :: Ptr VkAttachmentLoadOp -> VkAttachmentLoadOp -> IO ()
peek :: Ptr VkAttachmentLoadOp -> IO VkAttachmentLoadOp
$cpeek :: Ptr VkAttachmentLoadOp -> IO VkAttachmentLoadOp
pokeByteOff :: forall b. Ptr b -> Int -> VkAttachmentLoadOp -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkAttachmentLoadOp -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkAttachmentLoadOp
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkAttachmentLoadOp
pokeElemOff :: Ptr VkAttachmentLoadOp -> Int -> VkAttachmentLoadOp -> IO ()
$cpokeElemOff :: Ptr VkAttachmentLoadOp -> Int -> VkAttachmentLoadOp -> IO ()
peekElemOff :: Ptr VkAttachmentLoadOp -> Int -> IO VkAttachmentLoadOp
$cpeekElemOff :: Ptr VkAttachmentLoadOp -> Int -> IO VkAttachmentLoadOp
alignment :: VkAttachmentLoadOp -> Int
$calignment :: VkAttachmentLoadOp -> Int
sizeOf :: VkAttachmentLoadOp -> Int
$csizeOf :: VkAttachmentLoadOp -> Int
Storable)
instance Show VkAttachmentLoadOp where
showsPrec :: Int -> VkAttachmentLoadOp -> ShowS
showsPrec Int
_ VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_LOAD
= String -> ShowS
showString String
"VK_ATTACHMENT_LOAD_OP_LOAD"
showsPrec Int
_ VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_CLEAR
= String -> ShowS
showString String
"VK_ATTACHMENT_LOAD_OP_CLEAR"
showsPrec Int
_ VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_DONT_CARE
= String -> ShowS
showString String
"VK_ATTACHMENT_LOAD_OP_DONT_CARE"
showsPrec Int
p (VkAttachmentLoadOp Int32
x)
= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
(String -> ShowS
showString String
"VkAttachmentLoadOp " 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 VkAttachmentLoadOp where
readPrec :: ReadPrec VkAttachmentLoadOp
readPrec
= ReadPrec VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall a. ReadPrec a -> ReadPrec a
parens
([(String, ReadPrec VkAttachmentLoadOp)]
-> ReadPrec VkAttachmentLoadOp
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
[(String
"VK_ATTACHMENT_LOAD_OP_LOAD", VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_LOAD),
(String
"VK_ATTACHMENT_LOAD_OP_CLEAR", VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_CLEAR),
(String
"VK_ATTACHMENT_LOAD_OP_DONT_CARE",
VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentLoadOp
VK_ATTACHMENT_LOAD_OP_DONT_CARE)]
ReadPrec VkAttachmentLoadOp
-> ReadPrec VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
(Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkAttachmentLoadOp") ReadPrec ()
-> ReadPrec VkAttachmentLoadOp -> ReadPrec VkAttachmentLoadOp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Int32 -> VkAttachmentLoadOp
VkAttachmentLoadOp (Int32 -> VkAttachmentLoadOp)
-> ReadPrec Int32 -> ReadPrec VkAttachmentLoadOp
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_ATTACHMENT_LOAD_OP_LOAD :: VkAttachmentLoadOp
pattern $bVK_ATTACHMENT_LOAD_OP_LOAD :: VkAttachmentLoadOp
$mVK_ATTACHMENT_LOAD_OP_LOAD :: forall {r}. VkAttachmentLoadOp -> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_LOAD_OP_LOAD = VkAttachmentLoadOp 0
pattern VK_ATTACHMENT_LOAD_OP_CLEAR :: VkAttachmentLoadOp
pattern $bVK_ATTACHMENT_LOAD_OP_CLEAR :: VkAttachmentLoadOp
$mVK_ATTACHMENT_LOAD_OP_CLEAR :: forall {r}. VkAttachmentLoadOp -> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_LOAD_OP_CLEAR = VkAttachmentLoadOp 1
pattern VK_ATTACHMENT_LOAD_OP_DONT_CARE :: VkAttachmentLoadOp
pattern $bVK_ATTACHMENT_LOAD_OP_DONT_CARE :: VkAttachmentLoadOp
$mVK_ATTACHMENT_LOAD_OP_DONT_CARE :: forall {r}. VkAttachmentLoadOp -> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_LOAD_OP_DONT_CARE = VkAttachmentLoadOp 2
newtype VkAttachmentStoreOp = VkAttachmentStoreOp Int32
deriving (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
(VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> Eq VkAttachmentStoreOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c/= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
== :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c== :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
Eq, Eq VkAttachmentStoreOp
Eq VkAttachmentStoreOp
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Ordering)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool)
-> (VkAttachmentStoreOp
-> VkAttachmentStoreOp -> VkAttachmentStoreOp)
-> (VkAttachmentStoreOp
-> VkAttachmentStoreOp -> VkAttachmentStoreOp)
-> Ord VkAttachmentStoreOp
VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
VkAttachmentStoreOp -> VkAttachmentStoreOp -> Ordering
VkAttachmentStoreOp -> VkAttachmentStoreOp -> VkAttachmentStoreOp
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 :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> VkAttachmentStoreOp
$cmin :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> VkAttachmentStoreOp
max :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> VkAttachmentStoreOp
$cmax :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> VkAttachmentStoreOp
>= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c>= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
> :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c> :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
<= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c<= :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
< :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
$c< :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Bool
compare :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Ordering
$ccompare :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> Ordering
Ord, Int -> VkAttachmentStoreOp
VkAttachmentStoreOp -> Int
VkAttachmentStoreOp -> [VkAttachmentStoreOp]
VkAttachmentStoreOp -> VkAttachmentStoreOp
VkAttachmentStoreOp -> VkAttachmentStoreOp -> [VkAttachmentStoreOp]
VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> [VkAttachmentStoreOp]
(VkAttachmentStoreOp -> VkAttachmentStoreOp)
-> (VkAttachmentStoreOp -> VkAttachmentStoreOp)
-> (Int -> VkAttachmentStoreOp)
-> (VkAttachmentStoreOp -> Int)
-> (VkAttachmentStoreOp -> [VkAttachmentStoreOp])
-> (VkAttachmentStoreOp
-> VkAttachmentStoreOp -> [VkAttachmentStoreOp])
-> (VkAttachmentStoreOp
-> VkAttachmentStoreOp -> [VkAttachmentStoreOp])
-> (VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> [VkAttachmentStoreOp])
-> Enum VkAttachmentStoreOp
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 :: VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> [VkAttachmentStoreOp]
$cenumFromThenTo :: VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> VkAttachmentStoreOp
-> [VkAttachmentStoreOp]
enumFromTo :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> [VkAttachmentStoreOp]
$cenumFromTo :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> [VkAttachmentStoreOp]
enumFromThen :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> [VkAttachmentStoreOp]
$cenumFromThen :: VkAttachmentStoreOp -> VkAttachmentStoreOp -> [VkAttachmentStoreOp]
enumFrom :: VkAttachmentStoreOp -> [VkAttachmentStoreOp]
$cenumFrom :: VkAttachmentStoreOp -> [VkAttachmentStoreOp]
fromEnum :: VkAttachmentStoreOp -> Int
$cfromEnum :: VkAttachmentStoreOp -> Int
toEnum :: Int -> VkAttachmentStoreOp
$ctoEnum :: Int -> VkAttachmentStoreOp
pred :: VkAttachmentStoreOp -> VkAttachmentStoreOp
$cpred :: VkAttachmentStoreOp -> VkAttachmentStoreOp
succ :: VkAttachmentStoreOp -> VkAttachmentStoreOp
$csucc :: VkAttachmentStoreOp -> VkAttachmentStoreOp
Enum, Ptr VkAttachmentStoreOp -> IO VkAttachmentStoreOp
Ptr VkAttachmentStoreOp -> Int -> IO VkAttachmentStoreOp
Ptr VkAttachmentStoreOp -> Int -> VkAttachmentStoreOp -> IO ()
Ptr VkAttachmentStoreOp -> VkAttachmentStoreOp -> IO ()
VkAttachmentStoreOp -> Int
(VkAttachmentStoreOp -> Int)
-> (VkAttachmentStoreOp -> Int)
-> (Ptr VkAttachmentStoreOp -> Int -> IO VkAttachmentStoreOp)
-> (Ptr VkAttachmentStoreOp -> Int -> VkAttachmentStoreOp -> IO ())
-> (forall b. Ptr b -> Int -> IO VkAttachmentStoreOp)
-> (forall b. Ptr b -> Int -> VkAttachmentStoreOp -> IO ())
-> (Ptr VkAttachmentStoreOp -> IO VkAttachmentStoreOp)
-> (Ptr VkAttachmentStoreOp -> VkAttachmentStoreOp -> IO ())
-> Storable VkAttachmentStoreOp
forall b. Ptr b -> Int -> IO VkAttachmentStoreOp
forall b. Ptr b -> Int -> VkAttachmentStoreOp -> 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 VkAttachmentStoreOp -> VkAttachmentStoreOp -> IO ()
$cpoke :: Ptr VkAttachmentStoreOp -> VkAttachmentStoreOp -> IO ()
peek :: Ptr VkAttachmentStoreOp -> IO VkAttachmentStoreOp
$cpeek :: Ptr VkAttachmentStoreOp -> IO VkAttachmentStoreOp
pokeByteOff :: forall b. Ptr b -> Int -> VkAttachmentStoreOp -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkAttachmentStoreOp -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkAttachmentStoreOp
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkAttachmentStoreOp
pokeElemOff :: Ptr VkAttachmentStoreOp -> Int -> VkAttachmentStoreOp -> IO ()
$cpokeElemOff :: Ptr VkAttachmentStoreOp -> Int -> VkAttachmentStoreOp -> IO ()
peekElemOff :: Ptr VkAttachmentStoreOp -> Int -> IO VkAttachmentStoreOp
$cpeekElemOff :: Ptr VkAttachmentStoreOp -> Int -> IO VkAttachmentStoreOp
alignment :: VkAttachmentStoreOp -> Int
$calignment :: VkAttachmentStoreOp -> Int
sizeOf :: VkAttachmentStoreOp -> Int
$csizeOf :: VkAttachmentStoreOp -> Int
Storable)
instance Show VkAttachmentStoreOp where
showsPrec :: Int -> VkAttachmentStoreOp -> ShowS
showsPrec Int
_ VkAttachmentStoreOp
VK_ATTACHMENT_STORE_OP_STORE
= String -> ShowS
showString String
"VK_ATTACHMENT_STORE_OP_STORE"
showsPrec Int
_ VkAttachmentStoreOp
VK_ATTACHMENT_STORE_OP_DONT_CARE
= String -> ShowS
showString String
"VK_ATTACHMENT_STORE_OP_DONT_CARE"
showsPrec Int
p (VkAttachmentStoreOp Int32
x)
= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
(String -> ShowS
showString String
"VkAttachmentStoreOp " 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 VkAttachmentStoreOp where
readPrec :: ReadPrec VkAttachmentStoreOp
readPrec
= ReadPrec VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall a. ReadPrec a -> ReadPrec a
parens
([(String, ReadPrec VkAttachmentStoreOp)]
-> ReadPrec VkAttachmentStoreOp
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
[(String
"VK_ATTACHMENT_STORE_OP_STORE",
VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentStoreOp
VK_ATTACHMENT_STORE_OP_STORE),
(String
"VK_ATTACHMENT_STORE_OP_DONT_CARE",
VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkAttachmentStoreOp
VK_ATTACHMENT_STORE_OP_DONT_CARE)]
ReadPrec VkAttachmentStoreOp
-> ReadPrec VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
(Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkAttachmentStoreOp") ReadPrec ()
-> ReadPrec VkAttachmentStoreOp -> ReadPrec VkAttachmentStoreOp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Int32 -> VkAttachmentStoreOp
VkAttachmentStoreOp (Int32 -> VkAttachmentStoreOp)
-> ReadPrec Int32 -> ReadPrec VkAttachmentStoreOp
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_ATTACHMENT_STORE_OP_STORE :: VkAttachmentStoreOp
pattern $bVK_ATTACHMENT_STORE_OP_STORE :: VkAttachmentStoreOp
$mVK_ATTACHMENT_STORE_OP_STORE :: forall {r}.
VkAttachmentStoreOp -> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_STORE_OP_STORE = VkAttachmentStoreOp 0
pattern VK_ATTACHMENT_STORE_OP_DONT_CARE :: VkAttachmentStoreOp
pattern $bVK_ATTACHMENT_STORE_OP_DONT_CARE :: VkAttachmentStoreOp
$mVK_ATTACHMENT_STORE_OP_DONT_CARE :: forall {r}.
VkAttachmentStoreOp -> (Void# -> r) -> (Void# -> r) -> r
VK_ATTACHMENT_STORE_OP_DONT_CARE = VkAttachmentStoreOp 1