{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- This file was generated by wgpu-raw-hs-codegen on:
--   2021-08-25T10:02:03.522705
-- Using wgpu-native git hash:
--   b10496e7eed9349f0fd541e6dfe5029cb436de74 wgpu-native (v0.9.2.2)

module WGPU.Raw.Generated.Enum.WGPUErrorType where

import Data.Word (Word32)
import Foreign (Storable)
import Prelude (Eq, Num, Show)

newtype WGPUErrorType = WGPUErrorType Word32
  deriving (WGPUErrorType -> WGPUErrorType -> Bool
(WGPUErrorType -> WGPUErrorType -> Bool)
-> (WGPUErrorType -> WGPUErrorType -> Bool) -> Eq WGPUErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WGPUErrorType -> WGPUErrorType -> Bool
$c/= :: WGPUErrorType -> WGPUErrorType -> Bool
== :: WGPUErrorType -> WGPUErrorType -> Bool
$c== :: WGPUErrorType -> WGPUErrorType -> Bool
Eq, Int -> WGPUErrorType -> ShowS
[WGPUErrorType] -> ShowS
WGPUErrorType -> String
(Int -> WGPUErrorType -> ShowS)
-> (WGPUErrorType -> String)
-> ([WGPUErrorType] -> ShowS)
-> Show WGPUErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WGPUErrorType] -> ShowS
$cshowList :: [WGPUErrorType] -> ShowS
show :: WGPUErrorType -> String
$cshow :: WGPUErrorType -> String
showsPrec :: Int -> WGPUErrorType -> ShowS
$cshowsPrec :: Int -> WGPUErrorType -> ShowS
Show, Integer -> WGPUErrorType
WGPUErrorType -> WGPUErrorType
WGPUErrorType -> WGPUErrorType -> WGPUErrorType
(WGPUErrorType -> WGPUErrorType -> WGPUErrorType)
-> (WGPUErrorType -> WGPUErrorType -> WGPUErrorType)
-> (WGPUErrorType -> WGPUErrorType -> WGPUErrorType)
-> (WGPUErrorType -> WGPUErrorType)
-> (WGPUErrorType -> WGPUErrorType)
-> (WGPUErrorType -> WGPUErrorType)
-> (Integer -> WGPUErrorType)
-> Num WGPUErrorType
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> WGPUErrorType
$cfromInteger :: Integer -> WGPUErrorType
signum :: WGPUErrorType -> WGPUErrorType
$csignum :: WGPUErrorType -> WGPUErrorType
abs :: WGPUErrorType -> WGPUErrorType
$cabs :: WGPUErrorType -> WGPUErrorType
negate :: WGPUErrorType -> WGPUErrorType
$cnegate :: WGPUErrorType -> WGPUErrorType
* :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
$c* :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
- :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
$c- :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
+ :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
$c+ :: WGPUErrorType -> WGPUErrorType -> WGPUErrorType
Num, Ptr b -> Int -> IO WGPUErrorType
Ptr b -> Int -> WGPUErrorType -> IO ()
Ptr WGPUErrorType -> IO WGPUErrorType
Ptr WGPUErrorType -> Int -> IO WGPUErrorType
Ptr WGPUErrorType -> Int -> WGPUErrorType -> IO ()
Ptr WGPUErrorType -> WGPUErrorType -> IO ()
WGPUErrorType -> Int
(WGPUErrorType -> Int)
-> (WGPUErrorType -> Int)
-> (Ptr WGPUErrorType -> Int -> IO WGPUErrorType)
-> (Ptr WGPUErrorType -> Int -> WGPUErrorType -> IO ())
-> (forall b. Ptr b -> Int -> IO WGPUErrorType)
-> (forall b. Ptr b -> Int -> WGPUErrorType -> IO ())
-> (Ptr WGPUErrorType -> IO WGPUErrorType)
-> (Ptr WGPUErrorType -> WGPUErrorType -> IO ())
-> Storable WGPUErrorType
forall b. Ptr b -> Int -> IO WGPUErrorType
forall b. Ptr b -> Int -> WGPUErrorType -> 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 WGPUErrorType -> WGPUErrorType -> IO ()
$cpoke :: Ptr WGPUErrorType -> WGPUErrorType -> IO ()
peek :: Ptr WGPUErrorType -> IO WGPUErrorType
$cpeek :: Ptr WGPUErrorType -> IO WGPUErrorType
pokeByteOff :: Ptr b -> Int -> WGPUErrorType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> WGPUErrorType -> IO ()
peekByteOff :: Ptr b -> Int -> IO WGPUErrorType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO WGPUErrorType
pokeElemOff :: Ptr WGPUErrorType -> Int -> WGPUErrorType -> IO ()
$cpokeElemOff :: Ptr WGPUErrorType -> Int -> WGPUErrorType -> IO ()
peekElemOff :: Ptr WGPUErrorType -> Int -> IO WGPUErrorType
$cpeekElemOff :: Ptr WGPUErrorType -> Int -> IO WGPUErrorType
alignment :: WGPUErrorType -> Int
$calignment :: WGPUErrorType -> Int
sizeOf :: WGPUErrorType -> Int
$csizeOf :: WGPUErrorType -> Int
Storable)

pattern NoError :: forall a. (Eq a, Num a) => a
pattern $bNoError :: a
$mNoError :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
NoError = 0x00000000

pattern Validation :: forall a. (Eq a, Num a) => a
pattern $bValidation :: a
$mValidation :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
Validation = 0x00000001

pattern OutOfMemory :: forall a. (Eq a, Num a) => a
pattern $bOutOfMemory :: a
$mOutOfMemory :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
OutOfMemory = 0x00000002

pattern Unknown :: forall a. (Eq a, Num a) => a
pattern $bUnknown :: a
$mUnknown :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
Unknown = 0x00000003

pattern DeviceLost :: forall a. (Eq a, Num a) => a
pattern $bDeviceLost :: a
$mDeviceLost :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
DeviceLost = 0x00000004