module Data.SpirV.Enum.KernelProfilingInfo where import Data.Bits (Bits) import Data.String (IsString(..)) import Data.Word (Word32) import Foreign (Storable(..)) import GHC.Read (Read(..)) import Text.ParserCombinators.ReadPrec (pfail) import qualified GHC.Read as Read import qualified Text.Read.Lex as Lex newtype KernelProfilingInfo = KernelProfilingInfo Word32 deriving (Eq, Ord, Storable, Bits) pattern CmdExecTime :: KernelProfilingInfo pattern CmdExecTime = KernelProfilingInfo 0x1 toName :: IsString a => KernelProfilingInfo -> a toName x = case x of CmdExecTime -> "CmdExecTime" unknown -> fromString $ "KernelProfilingInfo " ++ show unknown instance Show KernelProfilingInfo where show = toName fromName :: (IsString a, Eq a) => a -> Maybe KernelProfilingInfo fromName x = case x of "CmdExecTime" -> Just CmdExecTime _unknown -> Nothing instance Read KernelProfilingInfo where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s