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