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