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