module Data.SpirV.Enum.FPFastMathMode 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 FPFastMathMode = FPFastMathMode Word32 deriving (Eq, Ord, Storable, Bits) pattern NotNaN :: FPFastMathMode pattern NotNaN = FPFastMathMode 0x1 pattern NotInf :: FPFastMathMode pattern NotInf = FPFastMathMode 0x2 pattern NSZ :: FPFastMathMode pattern NSZ = FPFastMathMode 0x4 pattern AllowRecip :: FPFastMathMode pattern AllowRecip = FPFastMathMode 0x8 pattern Fast :: FPFastMathMode pattern Fast = FPFastMathMode 0x10 pattern AllowContractFastINTEL :: FPFastMathMode pattern AllowContractFastINTEL = FPFastMathMode 0x10000 pattern AllowReassocINTEL :: FPFastMathMode pattern AllowReassocINTEL = FPFastMathMode 0x20000 toName :: IsString a => FPFastMathMode -> a toName x = case x of NotNaN -> "NotNaN" NotInf -> "NotInf" NSZ -> "NSZ" AllowRecip -> "AllowRecip" Fast -> "Fast" AllowContractFastINTEL -> "AllowContractFastINTEL" AllowReassocINTEL -> "AllowReassocINTEL" unknown -> fromString $ "FPFastMathMode " ++ show unknown instance Show FPFastMathMode where show = toName fromName :: (IsString a, Eq a) => a -> Maybe FPFastMathMode fromName x = case x of "NotNaN" -> Just NotNaN "NotInf" -> Just NotInf "NSZ" -> Just NSZ "AllowRecip" -> Just AllowRecip "Fast" -> Just Fast "AllowContractFastINTEL" -> Just AllowContractFastINTEL "AllowReassocINTEL" -> Just AllowReassocINTEL _unknown -> Nothing instance Read FPFastMathMode where readPrec = Read.parens do Lex.Ident s <- Read.lexP maybe pfail pure $ fromName s