module Data.SpirV.Enum.MemoryModel 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 MemoryModel = MemoryModel Word32 deriving (Eq, Ord, Storable) pattern Simple :: MemoryModel pattern Simple = MemoryModel 0 pattern GLSL450 :: MemoryModel pattern GLSL450 = MemoryModel 1 pattern OpenCL :: MemoryModel pattern OpenCL = MemoryModel 2 pattern Vulkan :: MemoryModel pattern Vulkan = MemoryModel 3 pattern VulkanKHR :: MemoryModel pattern VulkanKHR = MemoryModel 3 toName :: IsString a => MemoryModel -> a toName x = case x of Simple -> "Simple" GLSL450 -> "GLSL450" OpenCL -> "OpenCL" Vulkan -> "Vulkan" VulkanKHR -> "VulkanKHR" unknown -> fromString $ "MemoryModel " ++ show unknown instance Show MemoryModel where show = toName fromName :: (IsString a, Eq a) => a -> Maybe MemoryModel fromName x = case x of "Simple" -> Just Simple "GLSL450" -> Just GLSL450 "OpenCL" -> Just OpenCL "Vulkan" -> Just Vulkan "VulkanKHR" -> Just VulkanKHR _unknown -> Nothing instance Read MemoryModel where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s