{-# language CPP #-}
module Vulkan.Core12.Enums.DriverId  (DriverId( DRIVER_ID_AMD_PROPRIETARY
                                              , DRIVER_ID_AMD_OPEN_SOURCE
                                              , DRIVER_ID_MESA_RADV
                                              , DRIVER_ID_NVIDIA_PROPRIETARY
                                              , DRIVER_ID_INTEL_PROPRIETARY_WINDOWS
                                              , DRIVER_ID_INTEL_OPEN_SOURCE_MESA
                                              , DRIVER_ID_IMAGINATION_PROPRIETARY
                                              , DRIVER_ID_QUALCOMM_PROPRIETARY
                                              , DRIVER_ID_ARM_PROPRIETARY
                                              , DRIVER_ID_GOOGLE_SWIFTSHADER
                                              , DRIVER_ID_GGP_PROPRIETARY
                                              , DRIVER_ID_BROADCOM_PROPRIETARY
                                              , DRIVER_ID_MESA_LLVMPIPE
                                              , DRIVER_ID_MOLTENVK
                                              , ..
                                              )) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
-- | VkDriverId - Khronos driver IDs
--
-- = Description
--
-- Note
--
-- Khronos driver IDs may be allocated by vendors at any time. There may be
-- multiple driver IDs for the same vendor, representing different drivers
-- (for e.g. different platforms, proprietary or open source, etc.). Only
-- the latest canonical versions of this Specification, of the
-- corresponding @vk.xml@ API Registry, and of the corresponding
-- @vulkan_core.h@ header file /must/ contain all reserved Khronos driver
-- IDs.
--
-- Only driver IDs registered with Khronos are given symbolic names. There
-- /may/ be unregistered driver IDs returned.
--
-- = See Also
--
-- 'Vulkan.Core12.Promoted_From_VK_KHR_driver_properties.PhysicalDeviceDriverProperties',
-- 'Vulkan.Core12.PhysicalDeviceVulkan12Properties'
newtype DriverId = DriverId Int32
  deriving newtype (DriverId -> DriverId -> Bool
(DriverId -> DriverId -> Bool)
-> (DriverId -> DriverId -> Bool) -> Eq DriverId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DriverId -> DriverId -> Bool
$c/= :: DriverId -> DriverId -> Bool
== :: DriverId -> DriverId -> Bool
$c== :: DriverId -> DriverId -> Bool
Eq, Eq DriverId
Eq DriverId =>
(DriverId -> DriverId -> Ordering)
-> (DriverId -> DriverId -> Bool)
-> (DriverId -> DriverId -> Bool)
-> (DriverId -> DriverId -> Bool)
-> (DriverId -> DriverId -> Bool)
-> (DriverId -> DriverId -> DriverId)
-> (DriverId -> DriverId -> DriverId)
-> Ord DriverId
DriverId -> DriverId -> Bool
DriverId -> DriverId -> Ordering
DriverId -> DriverId -> DriverId
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 :: DriverId -> DriverId -> DriverId
$cmin :: DriverId -> DriverId -> DriverId
max :: DriverId -> DriverId -> DriverId
$cmax :: DriverId -> DriverId -> DriverId
>= :: DriverId -> DriverId -> Bool
$c>= :: DriverId -> DriverId -> Bool
> :: DriverId -> DriverId -> Bool
$c> :: DriverId -> DriverId -> Bool
<= :: DriverId -> DriverId -> Bool
$c<= :: DriverId -> DriverId -> Bool
< :: DriverId -> DriverId -> Bool
$c< :: DriverId -> DriverId -> Bool
compare :: DriverId -> DriverId -> Ordering
$ccompare :: DriverId -> DriverId -> Ordering
$cp1Ord :: Eq DriverId
Ord, Ptr b -> Int -> IO DriverId
Ptr b -> Int -> DriverId -> IO ()
Ptr DriverId -> IO DriverId
Ptr DriverId -> Int -> IO DriverId
Ptr DriverId -> Int -> DriverId -> IO ()
Ptr DriverId -> DriverId -> IO ()
DriverId -> Int
(DriverId -> Int)
-> (DriverId -> Int)
-> (Ptr DriverId -> Int -> IO DriverId)
-> (Ptr DriverId -> Int -> DriverId -> IO ())
-> (forall b. Ptr b -> Int -> IO DriverId)
-> (forall b. Ptr b -> Int -> DriverId -> IO ())
-> (Ptr DriverId -> IO DriverId)
-> (Ptr DriverId -> DriverId -> IO ())
-> Storable DriverId
forall b. Ptr b -> Int -> IO DriverId
forall b. Ptr b -> Int -> DriverId -> 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 DriverId -> DriverId -> IO ()
$cpoke :: Ptr DriverId -> DriverId -> IO ()
peek :: Ptr DriverId -> IO DriverId
$cpeek :: Ptr DriverId -> IO DriverId
pokeByteOff :: Ptr b -> Int -> DriverId -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DriverId -> IO ()
peekByteOff :: Ptr b -> Int -> IO DriverId
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DriverId
pokeElemOff :: Ptr DriverId -> Int -> DriverId -> IO ()
$cpokeElemOff :: Ptr DriverId -> Int -> DriverId -> IO ()
peekElemOff :: Ptr DriverId -> Int -> IO DriverId
$cpeekElemOff :: Ptr DriverId -> Int -> IO DriverId
alignment :: DriverId -> Int
$calignment :: DriverId -> Int
sizeOf :: DriverId -> Int
$csizeOf :: DriverId -> Int
Storable, DriverId
DriverId -> Zero DriverId
forall a. a -> Zero a
zero :: DriverId
$czero :: DriverId
Zero)
-- Note that the zero instance does not produce a valid value, passing 'zero' to Vulkan will result in an error

-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_AMD_PROPRIETARY"
pattern $bDRIVER_ID_AMD_PROPRIETARY :: DriverId
$mDRIVER_ID_AMD_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_AMD_PROPRIETARY = DriverId 1
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_AMD_OPEN_SOURCE"
pattern $bDRIVER_ID_AMD_OPEN_SOURCE :: DriverId
$mDRIVER_ID_AMD_OPEN_SOURCE :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_AMD_OPEN_SOURCE = DriverId 2
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_MESA_RADV"
pattern $bDRIVER_ID_MESA_RADV :: DriverId
$mDRIVER_ID_MESA_RADV :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_MESA_RADV = DriverId 3
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_NVIDIA_PROPRIETARY"
pattern $bDRIVER_ID_NVIDIA_PROPRIETARY :: DriverId
$mDRIVER_ID_NVIDIA_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_NVIDIA_PROPRIETARY = DriverId 4
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_INTEL_PROPRIETARY_WINDOWS"
pattern $bDRIVER_ID_INTEL_PROPRIETARY_WINDOWS :: DriverId
$mDRIVER_ID_INTEL_PROPRIETARY_WINDOWS :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_INTEL_PROPRIETARY_WINDOWS = DriverId 5
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_INTEL_OPEN_SOURCE_MESA"
pattern $bDRIVER_ID_INTEL_OPEN_SOURCE_MESA :: DriverId
$mDRIVER_ID_INTEL_OPEN_SOURCE_MESA :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_INTEL_OPEN_SOURCE_MESA = DriverId 6
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_IMAGINATION_PROPRIETARY"
pattern $bDRIVER_ID_IMAGINATION_PROPRIETARY :: DriverId
$mDRIVER_ID_IMAGINATION_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_IMAGINATION_PROPRIETARY = DriverId 7
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_QUALCOMM_PROPRIETARY"
pattern $bDRIVER_ID_QUALCOMM_PROPRIETARY :: DriverId
$mDRIVER_ID_QUALCOMM_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_QUALCOMM_PROPRIETARY = DriverId 8
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_ARM_PROPRIETARY"
pattern $bDRIVER_ID_ARM_PROPRIETARY :: DriverId
$mDRIVER_ID_ARM_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_ARM_PROPRIETARY = DriverId 9
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_GOOGLE_SWIFTSHADER"
pattern $bDRIVER_ID_GOOGLE_SWIFTSHADER :: DriverId
$mDRIVER_ID_GOOGLE_SWIFTSHADER :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_GOOGLE_SWIFTSHADER = DriverId 10
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_GGP_PROPRIETARY"
pattern $bDRIVER_ID_GGP_PROPRIETARY :: DriverId
$mDRIVER_ID_GGP_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_GGP_PROPRIETARY = DriverId 11
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_BROADCOM_PROPRIETARY"
pattern $bDRIVER_ID_BROADCOM_PROPRIETARY :: DriverId
$mDRIVER_ID_BROADCOM_PROPRIETARY :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_BROADCOM_PROPRIETARY = DriverId 12
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_MESA_LLVMPIPE"
pattern $bDRIVER_ID_MESA_LLVMPIPE :: DriverId
$mDRIVER_ID_MESA_LLVMPIPE :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_MESA_LLVMPIPE = DriverId 13
-- No documentation found for Nested "VkDriverId" "VK_DRIVER_ID_MOLTENVK"
pattern $bDRIVER_ID_MOLTENVK :: DriverId
$mDRIVER_ID_MOLTENVK :: forall r. DriverId -> (Void# -> r) -> (Void# -> r) -> r
DRIVER_ID_MOLTENVK = DriverId 14
{-# complete DRIVER_ID_AMD_PROPRIETARY,
             DRIVER_ID_AMD_OPEN_SOURCE,
             DRIVER_ID_MESA_RADV,
             DRIVER_ID_NVIDIA_PROPRIETARY,
             DRIVER_ID_INTEL_PROPRIETARY_WINDOWS,
             DRIVER_ID_INTEL_OPEN_SOURCE_MESA,
             DRIVER_ID_IMAGINATION_PROPRIETARY,
             DRIVER_ID_QUALCOMM_PROPRIETARY,
             DRIVER_ID_ARM_PROPRIETARY,
             DRIVER_ID_GOOGLE_SWIFTSHADER,
             DRIVER_ID_GGP_PROPRIETARY,
             DRIVER_ID_BROADCOM_PROPRIETARY,
             DRIVER_ID_MESA_LLVMPIPE,
             DRIVER_ID_MOLTENVK :: DriverId #-}

instance Show DriverId where
  showsPrec :: Int -> DriverId -> ShowS
showsPrec p :: Int
p = \case
    DRIVER_ID_AMD_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_AMD_PROPRIETARY"
    DRIVER_ID_AMD_OPEN_SOURCE -> String -> ShowS
showString "DRIVER_ID_AMD_OPEN_SOURCE"
    DRIVER_ID_MESA_RADV -> String -> ShowS
showString "DRIVER_ID_MESA_RADV"
    DRIVER_ID_NVIDIA_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_NVIDIA_PROPRIETARY"
    DRIVER_ID_INTEL_PROPRIETARY_WINDOWS -> String -> ShowS
showString "DRIVER_ID_INTEL_PROPRIETARY_WINDOWS"
    DRIVER_ID_INTEL_OPEN_SOURCE_MESA -> String -> ShowS
showString "DRIVER_ID_INTEL_OPEN_SOURCE_MESA"
    DRIVER_ID_IMAGINATION_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_IMAGINATION_PROPRIETARY"
    DRIVER_ID_QUALCOMM_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_QUALCOMM_PROPRIETARY"
    DRIVER_ID_ARM_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_ARM_PROPRIETARY"
    DRIVER_ID_GOOGLE_SWIFTSHADER -> String -> ShowS
showString "DRIVER_ID_GOOGLE_SWIFTSHADER"
    DRIVER_ID_GGP_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_GGP_PROPRIETARY"
    DRIVER_ID_BROADCOM_PROPRIETARY -> String -> ShowS
showString "DRIVER_ID_BROADCOM_PROPRIETARY"
    DRIVER_ID_MESA_LLVMPIPE -> String -> ShowS
showString "DRIVER_ID_MESA_LLVMPIPE"
    DRIVER_ID_MOLTENVK -> String -> ShowS
showString "DRIVER_ID_MOLTENVK"
    DriverId x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DriverId " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read DriverId where
  readPrec :: ReadPrec DriverId
readPrec = ReadPrec DriverId -> ReadPrec DriverId
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DriverId)] -> ReadPrec DriverId
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DRIVER_ID_AMD_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_AMD_PROPRIETARY)
                            , ("DRIVER_ID_AMD_OPEN_SOURCE", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_AMD_OPEN_SOURCE)
                            , ("DRIVER_ID_MESA_RADV", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_MESA_RADV)
                            , ("DRIVER_ID_NVIDIA_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_NVIDIA_PROPRIETARY)
                            , ("DRIVER_ID_INTEL_PROPRIETARY_WINDOWS", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_INTEL_PROPRIETARY_WINDOWS)
                            , ("DRIVER_ID_INTEL_OPEN_SOURCE_MESA", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_INTEL_OPEN_SOURCE_MESA)
                            , ("DRIVER_ID_IMAGINATION_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_IMAGINATION_PROPRIETARY)
                            , ("DRIVER_ID_QUALCOMM_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_QUALCOMM_PROPRIETARY)
                            , ("DRIVER_ID_ARM_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_ARM_PROPRIETARY)
                            , ("DRIVER_ID_GOOGLE_SWIFTSHADER", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_GOOGLE_SWIFTSHADER)
                            , ("DRIVER_ID_GGP_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_GGP_PROPRIETARY)
                            , ("DRIVER_ID_BROADCOM_PROPRIETARY", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_BROADCOM_PROPRIETARY)
                            , ("DRIVER_ID_MESA_LLVMPIPE", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_MESA_LLVMPIPE)
                            , ("DRIVER_ID_MOLTENVK", DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure DriverId
DRIVER_ID_MOLTENVK)]
                     ReadPrec DriverId -> ReadPrec DriverId -> ReadPrec DriverId
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec DriverId -> ReadPrec DriverId
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DriverId")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       DriverId -> ReadPrec DriverId
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> DriverId
DriverId Int32
v)))