module Data.SpirV.Enum.Scope where 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 Scope = Scope Word32 deriving (Eq, Ord, Storable) pattern CrossDevice :: Scope pattern CrossDevice = Scope 0 pattern Device :: Scope pattern Device = Scope 1 pattern Workgroup :: Scope pattern Workgroup = Scope 2 pattern Subgroup :: Scope pattern Subgroup = Scope 3 pattern Invocation :: Scope pattern Invocation = Scope 4 pattern QueueFamily :: Scope pattern QueueFamily = Scope 5 pattern QueueFamilyKHR :: Scope pattern QueueFamilyKHR = Scope 5 pattern ShaderCallKHR :: Scope pattern ShaderCallKHR = Scope 6 toName :: IsString a => Scope -> a toName x = case x of CrossDevice -> "CrossDevice" Device -> "Device" Workgroup -> "Workgroup" Subgroup -> "Subgroup" Invocation -> "Invocation" QueueFamily -> "QueueFamily" QueueFamilyKHR -> "QueueFamilyKHR" ShaderCallKHR -> "ShaderCallKHR" unknown -> fromString $ "Scope " ++ show unknown instance Show Scope where show = toName fromName :: (IsString a, Eq a) => a -> Maybe Scope fromName x = case x of "CrossDevice" -> Just CrossDevice "Device" -> Just Device "Workgroup" -> Just Workgroup "Subgroup" -> Just Subgroup "Invocation" -> Just Invocation "QueueFamily" -> Just QueueFamily "QueueFamilyKHR" -> Just QueueFamilyKHR "ShaderCallKHR" -> Just ShaderCallKHR _unknown -> Nothing instance Read Scope where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s