{-# language CPP #-}
module Vulkan.Core10.Enums.Result  (Result( SUCCESS
                                          , NOT_READY
                                          , TIMEOUT
                                          , EVENT_SET
                                          , EVENT_RESET
                                          , INCOMPLETE
                                          , ERROR_OUT_OF_HOST_MEMORY
                                          , ERROR_OUT_OF_DEVICE_MEMORY
                                          , ERROR_INITIALIZATION_FAILED
                                          , ERROR_DEVICE_LOST
                                          , ERROR_MEMORY_MAP_FAILED
                                          , ERROR_LAYER_NOT_PRESENT
                                          , ERROR_EXTENSION_NOT_PRESENT
                                          , ERROR_FEATURE_NOT_PRESENT
                                          , ERROR_INCOMPATIBLE_DRIVER
                                          , ERROR_TOO_MANY_OBJECTS
                                          , ERROR_FORMAT_NOT_SUPPORTED
                                          , ERROR_FRAGMENTED_POOL
                                          , ERROR_UNKNOWN
                                          , PIPELINE_COMPILE_REQUIRED_EXT
                                          , OPERATION_NOT_DEFERRED_KHR
                                          , OPERATION_DEFERRED_KHR
                                          , THREAD_DONE_KHR
                                          , THREAD_IDLE_KHR
                                          , ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT
                                          , ERROR_NOT_PERMITTED_EXT
                                          , ERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT
                                          , ERROR_INVALID_SHADER_NV
                                          , ERROR_VALIDATION_FAILED_EXT
                                          , ERROR_INCOMPATIBLE_DISPLAY_KHR
                                          , ERROR_OUT_OF_DATE_KHR
                                          , SUBOPTIMAL_KHR
                                          , ERROR_NATIVE_WINDOW_IN_USE_KHR
                                          , ERROR_SURFACE_LOST_KHR
                                          , ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS
                                          , ERROR_FRAGMENTATION
                                          , ERROR_INVALID_EXTERNAL_HANDLE
                                          , ERROR_OUT_OF_POOL_MEMORY
                                          , ..
                                          )) where
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showsPrec)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
newtype Result = Result Int32
  deriving newtype (Result -> Result -> Bool
(Result -> Result -> Bool)
-> (Result -> Result -> Bool) -> Eq Result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Eq Result
Eq Result =>
(Result -> Result -> Ordering)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Bool)
-> (Result -> Result -> Result)
-> (Result -> Result -> Result)
-> Ord Result
Result -> Result -> Bool
Result -> Result -> Ordering
Result -> Result -> Result
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 :: Result -> Result -> Result
$cmin :: Result -> Result -> Result
max :: Result -> Result -> Result
$cmax :: Result -> Result -> Result
>= :: Result -> Result -> Bool
$c>= :: Result -> Result -> Bool
> :: Result -> Result -> Bool
$c> :: Result -> Result -> Bool
<= :: Result -> Result -> Bool
$c<= :: Result -> Result -> Bool
< :: Result -> Result -> Bool
$c< :: Result -> Result -> Bool
compare :: Result -> Result -> Ordering
$ccompare :: Result -> Result -> Ordering
$cp1Ord :: Eq Result
Ord, Ptr b -> Int -> IO Result
Ptr b -> Int -> Result -> IO ()
Ptr Result -> IO Result
Ptr Result -> Int -> IO Result
Ptr Result -> Int -> Result -> IO ()
Ptr Result -> Result -> IO ()
Result -> Int
(Result -> Int)
-> (Result -> Int)
-> (Ptr Result -> Int -> IO Result)
-> (Ptr Result -> Int -> Result -> IO ())
-> (forall b. Ptr b -> Int -> IO Result)
-> (forall b. Ptr b -> Int -> Result -> IO ())
-> (Ptr Result -> IO Result)
-> (Ptr Result -> Result -> IO ())
-> Storable Result
forall b. Ptr b -> Int -> IO Result
forall b. Ptr b -> Int -> Result -> 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 Result -> Result -> IO ()
$cpoke :: Ptr Result -> Result -> IO ()
peek :: Ptr Result -> IO Result
$cpeek :: Ptr Result -> IO Result
pokeByteOff :: Ptr b -> Int -> Result -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Result -> IO ()
peekByteOff :: Ptr b -> Int -> IO Result
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Result
pokeElemOff :: Ptr Result -> Int -> Result -> IO ()
$cpokeElemOff :: Ptr Result -> Int -> Result -> IO ()
peekElemOff :: Ptr Result -> Int -> IO Result
$cpeekElemOff :: Ptr Result -> Int -> IO Result
alignment :: Result -> Int
$calignment :: Result -> Int
sizeOf :: Result -> Int
$csizeOf :: Result -> Int
Storable, Result
Result -> Zero Result
forall a. a -> Zero a
zero :: Result
$czero :: Result
Zero)
pattern $bSUCCESS :: Result
$mSUCCESS :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
SUCCESS                              = Result 0
pattern $bNOT_READY :: Result
$mNOT_READY :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
NOT_READY                            = Result 1
pattern $bTIMEOUT :: Result
$mTIMEOUT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
TIMEOUT                              = Result 2
pattern $bEVENT_SET :: Result
$mEVENT_SET :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
EVENT_SET                            = Result 3
pattern $bEVENT_RESET :: Result
$mEVENT_RESET :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
EVENT_RESET                          = Result 4
pattern $bINCOMPLETE :: Result
$mINCOMPLETE :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
INCOMPLETE                           = Result 5
pattern $bERROR_OUT_OF_HOST_MEMORY :: Result
$mERROR_OUT_OF_HOST_MEMORY :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_OUT_OF_HOST_MEMORY             = Result (-1)
pattern $bERROR_OUT_OF_DEVICE_MEMORY :: Result
$mERROR_OUT_OF_DEVICE_MEMORY :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_OUT_OF_DEVICE_MEMORY           = Result (-2)
pattern $bERROR_INITIALIZATION_FAILED :: Result
$mERROR_INITIALIZATION_FAILED :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INITIALIZATION_FAILED          = Result (-3)
pattern $bERROR_DEVICE_LOST :: Result
$mERROR_DEVICE_LOST :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_DEVICE_LOST                    = Result (-4)
pattern $bERROR_MEMORY_MAP_FAILED :: Result
$mERROR_MEMORY_MAP_FAILED :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_MEMORY_MAP_FAILED              = Result (-5)
pattern $bERROR_LAYER_NOT_PRESENT :: Result
$mERROR_LAYER_NOT_PRESENT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_LAYER_NOT_PRESENT              = Result (-6)
pattern $bERROR_EXTENSION_NOT_PRESENT :: Result
$mERROR_EXTENSION_NOT_PRESENT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_EXTENSION_NOT_PRESENT          = Result (-7)
pattern $bERROR_FEATURE_NOT_PRESENT :: Result
$mERROR_FEATURE_NOT_PRESENT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_FEATURE_NOT_PRESENT            = Result (-8)
pattern $bERROR_INCOMPATIBLE_DRIVER :: Result
$mERROR_INCOMPATIBLE_DRIVER :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INCOMPATIBLE_DRIVER            = Result (-9)
pattern $bERROR_TOO_MANY_OBJECTS :: Result
$mERROR_TOO_MANY_OBJECTS :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_TOO_MANY_OBJECTS               = Result (-10)
pattern $bERROR_FORMAT_NOT_SUPPORTED :: Result
$mERROR_FORMAT_NOT_SUPPORTED :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_FORMAT_NOT_SUPPORTED           = Result (-11)
pattern $bERROR_FRAGMENTED_POOL :: Result
$mERROR_FRAGMENTED_POOL :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_FRAGMENTED_POOL                = Result (-12)
pattern $bERROR_UNKNOWN :: Result
$mERROR_UNKNOWN :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_UNKNOWN                        = Result (-13)
pattern $bPIPELINE_COMPILE_REQUIRED_EXT :: Result
$mPIPELINE_COMPILE_REQUIRED_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
PIPELINE_COMPILE_REQUIRED_EXT        = Result 1000297000
pattern $bOPERATION_NOT_DEFERRED_KHR :: Result
$mOPERATION_NOT_DEFERRED_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
OPERATION_NOT_DEFERRED_KHR           = Result 1000268003
pattern $bOPERATION_DEFERRED_KHR :: Result
$mOPERATION_DEFERRED_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
OPERATION_DEFERRED_KHR               = Result 1000268002
pattern $bTHREAD_DONE_KHR :: Result
$mTHREAD_DONE_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
THREAD_DONE_KHR                      = Result 1000268001
pattern $bTHREAD_IDLE_KHR :: Result
$mTHREAD_IDLE_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
THREAD_IDLE_KHR                      = Result 1000268000
pattern $bERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT :: Result
$mERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT = Result (-1000255000)
pattern $bERROR_NOT_PERMITTED_EXT :: Result
$mERROR_NOT_PERMITTED_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_NOT_PERMITTED_EXT              = Result (-1000174001)
pattern $bERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT :: Result
$mERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT = Result (-1000158000)
pattern $bERROR_INVALID_SHADER_NV :: Result
$mERROR_INVALID_SHADER_NV :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INVALID_SHADER_NV              = Result (-1000012000)
pattern $bERROR_VALIDATION_FAILED_EXT :: Result
$mERROR_VALIDATION_FAILED_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_VALIDATION_FAILED_EXT          = Result (-1000011001)
pattern $bERROR_INCOMPATIBLE_DISPLAY_KHR :: Result
$mERROR_INCOMPATIBLE_DISPLAY_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INCOMPATIBLE_DISPLAY_KHR       = Result (-1000003001)
pattern $bERROR_OUT_OF_DATE_KHR :: Result
$mERROR_OUT_OF_DATE_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_OUT_OF_DATE_KHR                = Result (-1000001004)
pattern $bSUBOPTIMAL_KHR :: Result
$mSUBOPTIMAL_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
SUBOPTIMAL_KHR                       = Result 1000001003
pattern $bERROR_NATIVE_WINDOW_IN_USE_KHR :: Result
$mERROR_NATIVE_WINDOW_IN_USE_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_NATIVE_WINDOW_IN_USE_KHR       = Result (-1000000001)
pattern $bERROR_SURFACE_LOST_KHR :: Result
$mERROR_SURFACE_LOST_KHR :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_SURFACE_LOST_KHR               = Result (-1000000000)
pattern $bERROR_INVALID_OPAQUE_CAPTURE_ADDRESS :: Result
$mERROR_INVALID_OPAQUE_CAPTURE_ADDRESS :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS = Result (-1000257000)
pattern $bERROR_FRAGMENTATION :: Result
$mERROR_FRAGMENTATION :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_FRAGMENTATION                  = Result (-1000161000)
pattern $bERROR_INVALID_EXTERNAL_HANDLE :: Result
$mERROR_INVALID_EXTERNAL_HANDLE :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_INVALID_EXTERNAL_HANDLE        = Result (-1000072003)
pattern $bERROR_OUT_OF_POOL_MEMORY :: Result
$mERROR_OUT_OF_POOL_MEMORY :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_OUT_OF_POOL_MEMORY             = Result (-1000069000)
{-# complete SUCCESS,
             NOT_READY,
             TIMEOUT,
             EVENT_SET,
             EVENT_RESET,
             INCOMPLETE,
             ERROR_OUT_OF_HOST_MEMORY,
             ERROR_OUT_OF_DEVICE_MEMORY,
             ERROR_INITIALIZATION_FAILED,
             ERROR_DEVICE_LOST,
             ERROR_MEMORY_MAP_FAILED,
             ERROR_LAYER_NOT_PRESENT,
             ERROR_EXTENSION_NOT_PRESENT,
             ERROR_FEATURE_NOT_PRESENT,
             ERROR_INCOMPATIBLE_DRIVER,
             ERROR_TOO_MANY_OBJECTS,
             ERROR_FORMAT_NOT_SUPPORTED,
             ERROR_FRAGMENTED_POOL,
             ERROR_UNKNOWN,
             PIPELINE_COMPILE_REQUIRED_EXT,
             OPERATION_NOT_DEFERRED_KHR,
             OPERATION_DEFERRED_KHR,
             THREAD_DONE_KHR,
             THREAD_IDLE_KHR,
             ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT,
             ERROR_NOT_PERMITTED_EXT,
             ERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT,
             ERROR_INVALID_SHADER_NV,
             ERROR_VALIDATION_FAILED_EXT,
             ERROR_INCOMPATIBLE_DISPLAY_KHR,
             ERROR_OUT_OF_DATE_KHR,
             SUBOPTIMAL_KHR,
             ERROR_NATIVE_WINDOW_IN_USE_KHR,
             ERROR_SURFACE_LOST_KHR,
             ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS,
             ERROR_FRAGMENTATION,
             ERROR_INVALID_EXTERNAL_HANDLE,
             ERROR_OUT_OF_POOL_MEMORY :: Result #-}
conNameResult :: String
conNameResult :: String
conNameResult = "Result"
enumPrefixResult :: String
enumPrefixResult :: String
enumPrefixResult = ""
showTableResult :: [(Result, String)]
showTableResult :: [(Result, String)]
showTableResult =
  [ (Result
SUCCESS                             , "SUCCESS")
  , (Result
NOT_READY                           , "NOT_READY")
  , (Result
TIMEOUT                             , "TIMEOUT")
  , (Result
EVENT_SET                           , "EVENT_SET")
  , (Result
EVENT_RESET                         , "EVENT_RESET")
  , (Result
INCOMPLETE                          , "INCOMPLETE")
  , (Result
ERROR_OUT_OF_HOST_MEMORY            , "ERROR_OUT_OF_HOST_MEMORY")
  , (Result
ERROR_OUT_OF_DEVICE_MEMORY          , "ERROR_OUT_OF_DEVICE_MEMORY")
  , (Result
ERROR_INITIALIZATION_FAILED         , "ERROR_INITIALIZATION_FAILED")
  , (Result
ERROR_DEVICE_LOST                   , "ERROR_DEVICE_LOST")
  , (Result
ERROR_MEMORY_MAP_FAILED             , "ERROR_MEMORY_MAP_FAILED")
  , (Result
ERROR_LAYER_NOT_PRESENT             , "ERROR_LAYER_NOT_PRESENT")
  , (Result
ERROR_EXTENSION_NOT_PRESENT         , "ERROR_EXTENSION_NOT_PRESENT")
  , (Result
ERROR_FEATURE_NOT_PRESENT           , "ERROR_FEATURE_NOT_PRESENT")
  , (Result
ERROR_INCOMPATIBLE_DRIVER           , "ERROR_INCOMPATIBLE_DRIVER")
  , (Result
ERROR_TOO_MANY_OBJECTS              , "ERROR_TOO_MANY_OBJECTS")
  , (Result
ERROR_FORMAT_NOT_SUPPORTED          , "ERROR_FORMAT_NOT_SUPPORTED")
  , (Result
ERROR_FRAGMENTED_POOL               , "ERROR_FRAGMENTED_POOL")
  , (Result
ERROR_UNKNOWN                       , "ERROR_UNKNOWN")
  , (Result
PIPELINE_COMPILE_REQUIRED_EXT       , "PIPELINE_COMPILE_REQUIRED_EXT")
  , (Result
OPERATION_NOT_DEFERRED_KHR          , "OPERATION_NOT_DEFERRED_KHR")
  , (Result
OPERATION_DEFERRED_KHR              , "OPERATION_DEFERRED_KHR")
  , (Result
THREAD_DONE_KHR                     , "THREAD_DONE_KHR")
  , (Result
THREAD_IDLE_KHR                     , "THREAD_IDLE_KHR")
  , (Result
ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT, "ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT")
  , (Result
ERROR_NOT_PERMITTED_EXT             , "ERROR_NOT_PERMITTED_EXT")
  , (Result
ERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT, "ERROR_INVALID_DRM_FORMAT_MODIFIER_PLANE_LAYOUT_EXT")
  , (Result
ERROR_INVALID_SHADER_NV             , "ERROR_INVALID_SHADER_NV")
  , (Result
ERROR_VALIDATION_FAILED_EXT         , "ERROR_VALIDATION_FAILED_EXT")
  , (Result
ERROR_INCOMPATIBLE_DISPLAY_KHR      , "ERROR_INCOMPATIBLE_DISPLAY_KHR")
  , (Result
ERROR_OUT_OF_DATE_KHR               , "ERROR_OUT_OF_DATE_KHR")
  , (Result
SUBOPTIMAL_KHR                      , "SUBOPTIMAL_KHR")
  , (Result
ERROR_NATIVE_WINDOW_IN_USE_KHR      , "ERROR_NATIVE_WINDOW_IN_USE_KHR")
  , (Result
ERROR_SURFACE_LOST_KHR              , "ERROR_SURFACE_LOST_KHR")
  , (Result
ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS, "ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS")
  , (Result
ERROR_FRAGMENTATION                 , "ERROR_FRAGMENTATION")
  , (Result
ERROR_INVALID_EXTERNAL_HANDLE       , "ERROR_INVALID_EXTERNAL_HANDLE")
  , (Result
ERROR_OUT_OF_POOL_MEMORY            , "ERROR_OUT_OF_POOL_MEMORY")
  ]
instance Show Result where
  showsPrec :: Int -> Result -> ShowS
showsPrec = String
-> [(Result, String)]
-> String
-> (Result -> Int32)
-> (Int32 -> ShowS)
-> Int
-> Result
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixResult [(Result, String)]
showTableResult String
conNameResult (\(Result x :: Int32
x) -> Int32
x) (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11)
instance Read Result where
  readPrec :: ReadPrec Result
readPrec = String
-> [(Result, String)]
-> String
-> (Int32 -> Result)
-> ReadPrec Result
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixResult [(Result, String)]
showTableResult String
conNameResult Int32 -> Result
Result