[Git][ghc/ghc][wip/fix-26109] 2 commits: Moving 'LowerBitsAreDefined' out of the autogenerated portion of the file

recursion-ninja pushed to branch wip/fix-26109 at Glasgow Haskell Compiler / GHC Commits: a522e725 by Recursion Ninja at 2025-08-08T13:33:17-04:00 Moving 'LowerBitsAreDefined' out of the autogenerated portion of the file - - - - - 3a9ec9d9 by Recursion Ninja at 2025-08-08T16:49:26-04:00 Partial extension of 'genprimopcode' to support 'LowerBitsAreDefined' - - - - - 7 changed files: - compiler/GHC/Builtin/primops.txt.pp - testsuite/tests/numeric/should_run/foundation.hs - utils/genprimopcode/Lexer.x - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/ParserM.hs - utils/genprimopcode/Syntax.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -148,6 +148,7 @@ defaults vector = [] deprecated_msg = {} -- A non-empty message indicates deprecation div_like = False -- Second argument expected to be non zero - used for tests + defined_bits = Nothing -- The number of bits the operation is defined for (if not all bits) -- Note [When do out-of-line primops go in primops.txt.pp] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1065,8 +1066,10 @@ primop CtzOp "ctz#" GenPrimOp Word# -> Word# primop BSwap16Op "byteSwap16#" GenPrimOp Word# -> Word# {Swap bytes in the lower 16 bits of a word. The higher bytes are undefined. } + with defined_bits = 16 primop BSwap32Op "byteSwap32#" GenPrimOp Word# -> Word# {Swap bytes in the lower 32 bits of a word. The higher bytes are undefined. } + with defined_bits = 32 primop BSwap64Op "byteSwap64#" GenPrimOp Word64# -> Word64# {Swap bytes in a 64 bits of a word.} primop BSwapOp "byteSwap#" GenPrimOp Word# -> Word# @@ -1074,10 +1077,13 @@ primop BSwapOp "byteSwap#" GenPrimOp Word# -> Word# primop BRev8Op "bitReverse8#" GenPrimOp Word# -> Word# {Reverse the order of the bits in a 8-bit word.} + with defined_bits = 8 primop BRev16Op "bitReverse16#" GenPrimOp Word# -> Word# {Reverse the order of the bits in a 16-bit word.} + with defined_bits = 16 primop BRev32Op "bitReverse32#" GenPrimOp Word# -> Word# {Reverse the order of the bits in a 32-bit word.} + with defined_bits = 32 primop BRev64Op "bitReverse64#" GenPrimOp Word64# -> Word64# {Reverse the order of the bits in a 64-bit word.} primop BRevOp "bitReverse#" GenPrimOp Word# -> Word# ===================================== testsuite/tests/numeric/should_run/foundation.hs ===================================== @@ -409,6 +409,33 @@ instance TestPrimop (Word# -> Int# -> Word#) where testPrimop s l r = Property s $ \(uWord -> a1) (uInt -> a2) -> (wWord (l a1 a2)) === wWord (r a1 a2) -} +-- | A special data-type for representing functions where, +-- since only some number of the lower bits are defined, +-- testing for strict equality in the undefined upper bits is not appropriate! +-- Without using this data-type, false-positive failures will be reported +-- when the undefined bit regions do not match, even though the equality of bits +-- in this undefined region has no bearing on correctness. +data LowerBitsAreDefined = + LowerBitsAreDefined + { definedLowerWidth :: Word + -- ^ The (strictly-non-negative) number of least-significant bits + -- for which the attached function is defined. + , undefinedBehavior :: (Word# -> Word#) + -- ^ Function with undefined behavior for some of its most significant bits. + } + +instance TestPrimop LowerBitsAreDefined where + testPrimop s l r = Property s $ \ (uWord#-> x0) -> + let -- Create a mask to unset all bits in the undefined area, + -- leaving set bits only in the area of defined behavior. + -- Since the upper bits are undefined, + -- if the function defines behavior for the lower N bits, + -- then /only/ the lower N bits are preserved, + -- and the upper WORDSIZE - N bits are discarded. + mask = bit (fromEnum (definedLowerWidth r)) - 1 + valL = wWord# (undefinedBehavior l x0) .&. mask + valR = wWord# (undefinedBehavior r x0) .&. mask + in valL === valR twoNonZero :: (a -> a -> b) -> a -> NonZero a -> b twoNonZero f x (NonZero y) = f x y @@ -673,34 +700,6 @@ testPrimops = Group "primop" , testPrimop "narrow32Word#" Primop.narrow32Word# Wrapper.narrow32Word# ] --- | A special data-type for representing functions where, --- since only some number of the lower bits are defined, --- testing for strict equality in the undefined upper bits is not appropriate! --- Without using this data-type, false-positive failures will be reported --- when the undefined bit regions do not match, even though the equality of bits --- in this undefined region has no bearing on correctness. -data LowerBitsAreDefined = - LowerBitsAreDefined - { definedLowerWidth :: Word - -- ^ The (strictly-non-negative) number of least-significant bits - -- for which the attached function is defined. - , undefinedBehavior :: (Word# -> Word#) - -- ^ Function with undefined behavior for some of its most significant bits. - } - -instance TestPrimop LowerBitsAreDefined where - testPrimop s l r = Property s $ \ (uWord#-> x0) -> - let -- Create a mask to unset all bits in the undefined area, - -- leaving set bits only in the area of defined behavior. - -- Since the upper bits are undefined, - -- if the function defines behavior for the lower N bits, - -- then /only/ the lower N bits are preserved, - -- and the upper WORDSIZE - N bits are discarded. - mask = bit (fromEnum (definedLowerWidth r)) - 1 - valL = wWord# (undefinedBehavior l x0) .&. mask - valR = wWord# (undefinedBehavior r x0) .&. mask - in valL === valR - instance TestPrimop (Char# -> Char# -> Int#) where testPrimop s l r = Property s $ \ (uChar#-> x0) (uChar#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1) ===================================== utils/genprimopcode/Lexer.x ===================================== @@ -56,6 +56,7 @@ words :- <0> "CanFail" { mkT TCanFail } <0> "ThrowsException" { mkT TThrowsException } <0> "ReadWriteEffect" { mkT TReadWriteEffect } + <0> "defined_bits" { mkT TDefinedBits } <0> "can_fail_warning" { mkT TCanFailWarnFlag } <0> "DoNotWarnCanFail" { mkT TDoNotWarnCanFail } <0> "WarnIfEffectIsCanFail" { mkT TWarnIfEffectIsCanFail } ===================================== utils/genprimopcode/Main.hs ===================================== @@ -10,6 +10,7 @@ module Main where import Parser import Syntax +import Control.Applicative (asum) import Data.Char import Data.List (union, intersperse, intercalate, nub, sort) import Data.Maybe ( catMaybes, mapMaybe ) @@ -753,7 +754,14 @@ gen_foundation_tests (Info _ entries) = let testPrimOpHow = if is_divLikeOp po then "testPrimopDivLike" else "testPrimop" - in Just $ intercalate " " [testPrimOpHow, "\"" ++ poName ++ "\"", wrap "Primop" poName, wrap "Wrapper" poName] + withDefinedBits qName = case mb_defined_bits po of + Nothing -> qName + Just bs -> concat ["(", show bs, " `LowerBitsAreDefined` ", qName, ")"] + in Just $ intercalate " " + [ testPrimOpHow + , "\"" ++ poName ++ "\"" + , withDefinedBits $ wrap "Primop" poName + , withDefinedBits $ wrap "Wrapper" poName] | otherwise = Nothing @@ -771,6 +779,17 @@ gen_foundation_tests (Info _ entries) divableTyCons = ["Int#", "Word#", "Word8#", "Word16#", "Word32#", "Word64#" ,"Int8#", "Int16#", "Int32#", "Int64#"] + + mb_defined_bits :: Entry -> Maybe Word + mb_defined_bits op@(PrimOpSpec{}) = + let opOpts = opts op + getDefBits :: Option -> Maybe Word + getDefBits (OptionDefinedBits x) = x + getDefBits _ = Nothing + in asum $ getDefBits <$> opOpts + mb_defined_bits _ = Nothing + + ------------------------------------------------------------------ -- Create PrimOpInfo text from PrimOpSpecs ----------------------- ------------------------------------------------------------------ ===================================== utils/genprimopcode/Parser.y ===================================== @@ -50,6 +50,7 @@ import AccessOps CanFail { TCanFail } ThrowsException { TThrowsException } ReadWriteEffect { TReadWriteEffect } + defined_bits { TDefinedBits } can_fail_warning { TCanFailWarnFlag } DoNotWarnCanFail { TDoNotWarnCanFail } WarnIfEffectIsCanFail { TWarnIfEffectIsCanFail } @@ -81,13 +82,14 @@ pOptions : pOption pOptions { $1 : $2 } | {- empty -} { [] } pOption :: { Option } -pOption : lowerName '=' false { OptionFalse $1 } - | lowerName '=' true { OptionTrue $1 } - | lowerName '=' pStuffBetweenBraces { OptionString $1 $3 } - | lowerName '=' integer { OptionInteger $1 $3 } - | vector '=' pVectorTemplate { OptionVector $3 } - | fixity '=' pInfix { OptionFixity $3 } - | effect '=' pEffect { OptionEffect $3 } +pOption : lowerName '=' false { OptionFalse $1 } + | lowerName '=' true { OptionTrue $1 } + | lowerName '=' pStuffBetweenBraces { OptionString $1 $3 } + | lowerName '=' integer { OptionInteger $1 $3 } + | vector '=' pVectorTemplate { OptionVector $3 } + | fixity '=' pInfix { OptionFixity $3 } + | effect '=' pEffect { OptionEffect $3 } + | defined_bits '=' pGoodBits { OptionDefinedBits $3 } | can_fail_warning '=' pPrimOpCanFailWarnFlag { OptionCanFailWarnFlag $3 } pInfix :: { Maybe Fixity } @@ -102,6 +104,10 @@ pEffect : NoEffect { NoEffect } | ThrowsException { ThrowsException } | ReadWriteEffect { ReadWriteEffect } +pGoodBits :: { Maybe Word } +pGoodBits : integer { Just $ toEnum $1 } + | nothing { Nothing } + pPrimOpCanFailWarnFlag :: { PrimOpCanFailWarnFlag } pPrimOpCanFailWarnFlag : DoNotWarnCanFail { DoNotWarnCanFail } | WarnIfEffectIsCanFail { WarnIfEffectIsCanFail } ===================================== utils/genprimopcode/ParserM.hs ===================================== @@ -116,6 +116,7 @@ data Token = TEOF | TCanFail | TThrowsException | TReadWriteEffect + | TDefinedBits | TCanFailWarnFlag | TDoNotWarnCanFail | TWarnIfEffectIsCanFail ===================================== utils/genprimopcode/Syntax.hs ===================================== @@ -76,6 +76,7 @@ data Option | OptionFixity (Maybe Fixity) -- fixity = infix{,l,r} <int> | Nothing | OptionEffect PrimOpEffect -- effect = NoEffect | DoNotSpeculate | CanFail | ThrowsException | ReadWriteEffect | FallibleReadWriteEffect | OptionCanFailWarnFlag PrimOpCanFailWarnFlag -- can_fail_warning = DoNotWarnCanFail | WarnIfEffectIsCanFail | YesWarnCanFail + | OptionDefinedBits (Maybe Word) -- defined_bits = Just 16 | Nothing deriving Show -- categorises primops @@ -196,6 +197,7 @@ get_attrib_name (OptionVector _) = "vector" get_attrib_name (OptionFixity _) = "fixity" get_attrib_name (OptionEffect _) = "effect" get_attrib_name (OptionCanFailWarnFlag _) = "can_fail_warning" +get_attrib_name (OptionDefinedBits _) = "defined_bits" lookup_attrib :: String -> [Option] -> Maybe Option lookup_attrib _ [] = Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/224fb5bd5e724226e1f9a2783cbf1c7... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/224fb5bd5e724226e1f9a2783cbf1c7... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
recursion-ninja (@recursion-ninja)