{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE Strict                     #-}
module Graphics.Vulkan.Types.Enum.InternalAllocationType
       (VkInternalAllocationType(VkInternalAllocationType,
                                 VK_INTERNAL_ALLOCATION_TYPE_EXECUTABLE))
       where
import Foreign.Storable                (Storable)
import GHC.Read                        (choose, expectP)
import Graphics.Vulkan.Marshal         (Int32)
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.2-extensions/html/vkspec.html#VkInternalAllocationType VkInternalAllocationType registry at www.khronos.org>
newtype VkInternalAllocationType = VkInternalAllocationType Int32
                                   deriving (VkInternalAllocationType -> VkInternalAllocationType -> Bool
(VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> (VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> Eq VkInternalAllocationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c/= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
== :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c== :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
Eq, Eq VkInternalAllocationType
Eq VkInternalAllocationType
-> (VkInternalAllocationType
    -> VkInternalAllocationType -> Ordering)
-> (VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> (VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> (VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> (VkInternalAllocationType -> VkInternalAllocationType -> Bool)
-> (VkInternalAllocationType
    -> VkInternalAllocationType -> VkInternalAllocationType)
-> (VkInternalAllocationType
    -> VkInternalAllocationType -> VkInternalAllocationType)
-> Ord VkInternalAllocationType
VkInternalAllocationType -> VkInternalAllocationType -> Bool
VkInternalAllocationType -> VkInternalAllocationType -> Ordering
VkInternalAllocationType
-> VkInternalAllocationType -> VkInternalAllocationType
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 :: VkInternalAllocationType
-> VkInternalAllocationType -> VkInternalAllocationType
$cmin :: VkInternalAllocationType
-> VkInternalAllocationType -> VkInternalAllocationType
max :: VkInternalAllocationType
-> VkInternalAllocationType -> VkInternalAllocationType
$cmax :: VkInternalAllocationType
-> VkInternalAllocationType -> VkInternalAllocationType
>= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c>= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
> :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c> :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
<= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c<= :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
< :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
$c< :: VkInternalAllocationType -> VkInternalAllocationType -> Bool
compare :: VkInternalAllocationType -> VkInternalAllocationType -> Ordering
$ccompare :: VkInternalAllocationType -> VkInternalAllocationType -> Ordering
Ord, Int -> VkInternalAllocationType
VkInternalAllocationType -> Int
VkInternalAllocationType -> [VkInternalAllocationType]
VkInternalAllocationType -> VkInternalAllocationType
VkInternalAllocationType
-> VkInternalAllocationType -> [VkInternalAllocationType]
VkInternalAllocationType
-> VkInternalAllocationType
-> VkInternalAllocationType
-> [VkInternalAllocationType]
(VkInternalAllocationType -> VkInternalAllocationType)
-> (VkInternalAllocationType -> VkInternalAllocationType)
-> (Int -> VkInternalAllocationType)
-> (VkInternalAllocationType -> Int)
-> (VkInternalAllocationType -> [VkInternalAllocationType])
-> (VkInternalAllocationType
    -> VkInternalAllocationType -> [VkInternalAllocationType])
-> (VkInternalAllocationType
    -> VkInternalAllocationType -> [VkInternalAllocationType])
-> (VkInternalAllocationType
    -> VkInternalAllocationType
    -> VkInternalAllocationType
    -> [VkInternalAllocationType])
-> Enum VkInternalAllocationType
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 :: VkInternalAllocationType
-> VkInternalAllocationType
-> VkInternalAllocationType
-> [VkInternalAllocationType]
$cenumFromThenTo :: VkInternalAllocationType
-> VkInternalAllocationType
-> VkInternalAllocationType
-> [VkInternalAllocationType]
enumFromTo :: VkInternalAllocationType
-> VkInternalAllocationType -> [VkInternalAllocationType]
$cenumFromTo :: VkInternalAllocationType
-> VkInternalAllocationType -> [VkInternalAllocationType]
enumFromThen :: VkInternalAllocationType
-> VkInternalAllocationType -> [VkInternalAllocationType]
$cenumFromThen :: VkInternalAllocationType
-> VkInternalAllocationType -> [VkInternalAllocationType]
enumFrom :: VkInternalAllocationType -> [VkInternalAllocationType]
$cenumFrom :: VkInternalAllocationType -> [VkInternalAllocationType]
fromEnum :: VkInternalAllocationType -> Int
$cfromEnum :: VkInternalAllocationType -> Int
toEnum :: Int -> VkInternalAllocationType
$ctoEnum :: Int -> VkInternalAllocationType
pred :: VkInternalAllocationType -> VkInternalAllocationType
$cpred :: VkInternalAllocationType -> VkInternalAllocationType
succ :: VkInternalAllocationType -> VkInternalAllocationType
$csucc :: VkInternalAllocationType -> VkInternalAllocationType
Enum, Ptr VkInternalAllocationType -> IO VkInternalAllocationType
Ptr VkInternalAllocationType -> Int -> IO VkInternalAllocationType
Ptr VkInternalAllocationType
-> Int -> VkInternalAllocationType -> IO ()
Ptr VkInternalAllocationType -> VkInternalAllocationType -> IO ()
VkInternalAllocationType -> Int
(VkInternalAllocationType -> Int)
-> (VkInternalAllocationType -> Int)
-> (Ptr VkInternalAllocationType
    -> Int -> IO VkInternalAllocationType)
-> (Ptr VkInternalAllocationType
    -> Int -> VkInternalAllocationType -> IO ())
-> (forall b. Ptr b -> Int -> IO VkInternalAllocationType)
-> (forall b. Ptr b -> Int -> VkInternalAllocationType -> IO ())
-> (Ptr VkInternalAllocationType -> IO VkInternalAllocationType)
-> (Ptr VkInternalAllocationType
    -> VkInternalAllocationType -> IO ())
-> Storable VkInternalAllocationType
forall b. Ptr b -> Int -> IO VkInternalAllocationType
forall b. Ptr b -> Int -> VkInternalAllocationType -> 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 VkInternalAllocationType -> VkInternalAllocationType -> IO ()
$cpoke :: Ptr VkInternalAllocationType -> VkInternalAllocationType -> IO ()
peek :: Ptr VkInternalAllocationType -> IO VkInternalAllocationType
$cpeek :: Ptr VkInternalAllocationType -> IO VkInternalAllocationType
pokeByteOff :: forall b. Ptr b -> Int -> VkInternalAllocationType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkInternalAllocationType -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkInternalAllocationType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkInternalAllocationType
pokeElemOff :: Ptr VkInternalAllocationType
-> Int -> VkInternalAllocationType -> IO ()
$cpokeElemOff :: Ptr VkInternalAllocationType
-> Int -> VkInternalAllocationType -> IO ()
peekElemOff :: Ptr VkInternalAllocationType -> Int -> IO VkInternalAllocationType
$cpeekElemOff :: Ptr VkInternalAllocationType -> Int -> IO VkInternalAllocationType
alignment :: VkInternalAllocationType -> Int
$calignment :: VkInternalAllocationType -> Int
sizeOf :: VkInternalAllocationType -> Int
$csizeOf :: VkInternalAllocationType -> Int
Storable)

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

pattern $bVK_INTERNAL_ALLOCATION_TYPE_EXECUTABLE :: VkInternalAllocationType
$mVK_INTERNAL_ALLOCATION_TYPE_EXECUTABLE :: forall {r}.
VkInternalAllocationType -> (Void# -> r) -> (Void# -> r) -> r
VK_INTERNAL_ALLOCATION_TYPE_EXECUTABLE =
        VkInternalAllocationType 0