[Git][ghc/ghc][master] 2 commits: JS: fix array index for registers
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c9fa3449 by Sylvain Henry at 2025-11-15T05:15:26-05:00 JS: fix array index for registers We used to store R32 in h$regs[-1]. While it's correct in JavaScript, fix this to store R32 in h$regs[0] instead. - - - - - 9e469909 by Sylvain Henry at 2025-11-15T05:15:26-05:00 JS: support more than 128 registers (#26558) The JS backend only supported 128 registers (JS variables/array slots used to pass function arguments). It failed in T26537 when 129 registers were required. This commit adds support for more than 128 registers: it is now limited to maxBound :: Int (compiler's Int). If we ever go above this threshold the compiler now panics with a more descriptive message. A few built-in JS functions were assuming 128 registers and have been rewritten to use loops. Note that loops are only used for "high" registers that are stored in an array: the 31 "low" registers are still handled with JS global variables and with explicit switch-cases to maintain good performance in the most common cases (i.e. few registers used). Adjusting the number of low registers is now easy: just one constant to adjust (GHC.StgToJS.Regs.lowRegsCount). No new test added: T26537 is used as a regression test instead. - - - - - 6 changed files: - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/Regs.hs - compiler/GHC/StgToJS/Rts/Rts.hs - compiler/GHC/StgToJS/Rts/Types.hs - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== compiler/GHC/StgToJS/Apply.hs ===================================== @@ -185,7 +185,7 @@ genApp ctx i args as' <- concatMapM genArg args ei <- varForEntryId i let ra = mconcat . reverse $ - zipWith (\r a -> toJExpr r |= a) [R1 ..] as' + zipWith (\r a -> toJExpr r |= a) regsFromR1 as' p <- pushLneFrame n ctx a <- adjSp 1 -- for the header (which will only be written when the thread is suspended) return (ra <> p <> a <> returnS ei, ExprCont) @@ -464,42 +464,31 @@ specTag spec = Bits.shiftL (specVars spec) 8 Bits..|. specArgs spec specTagExpr :: ApplySpec -> JStgExpr specTagExpr = toJExpr . specTag --- | Build arrays to quickly lookup apply functions +-- | Build functions to quickly lookup apply functions -- --- h$apply[r << 8 | n] = function application for r regs, n args --- h$paps[r] = partial application for r registers (number of args is in the object) +-- h$apply(r << 8 | n) = function application for r regs, n args +-- h$paps(r) = partial application for r registers (number of args is in the object) mkApplyArr :: JSM JStgStat mkApplyArr = - do mk_ap_gens <- jFor (|= zero_) (.<. Int 65536) preIncrS - \j -> hdApply .! j |= hdApGen - mk_pap_gens <- jFor (|= zero_) (.<. Int 128) preIncrS - \j -> hdPaps .! j |= hdPapGen + do paps_fun <- jFunction (name hdPapsStr) \(MkSolo i) -> pure $ SwitchStat i (map case_pap specPap) (returnS hdPapGen) + apply_fun <- jFunction (name hdApplyStr) \(MkSolo i) -> pure $ SwitchStat i (mapMaybe' case_apply applySpec) (returnS hdApGen) return $ mconcat - [ name hdApplyStr ||= toJExpr (JList []) - , name hdPapsStr ||= toJExpr (JList []) - , ApplStat (hdInitStatic .^ "push") - [ jLam' $ - mconcat - [ mk_ap_gens - , mk_pap_gens - , mconcat (map assignSpec applySpec) - , mconcat (map assignPap specPap) - ] - ] + [ paps_fun + , apply_fun ] where - assignSpec :: ApplySpec -> JStgStat - assignSpec spec = case specConv spec of + case_apply :: ApplySpec -> Maybe (JStgExpr,JStgStat) + case_apply spec = case specConv spec of -- both fast/slow (regs/stack) specialized apply functions have the same -- tags. We store the stack ones in the array because they are used as -- continuation stack frames. - StackConv -> hdApply .! specTagExpr spec |= specApplyExpr spec - RegsConv -> mempty + StackConv -> Just (specTagExpr spec, returnS (specApplyExpr spec)) + RegsConv -> Nothing hdPap_ = unpackFS hdPapStr_ - assignPap :: Int -> JStgStat - assignPap p = hdPaps .! toJExpr p |= global (mkFastString (hdPap_ ++ show p)) + case_pap :: Int -> (JStgExpr, JStgStat) + case_pap p = (toJExpr p, returnS $ global (mkFastString (hdPap_ ++ show p))) -- | Push a continuation on the stack -- @@ -619,7 +608,7 @@ genericStackApply cfg = closure info body -- compute new tag with consumed register values and args removed , newTag |= ((given_regs-needed_regs).<<.8) .|. (given_args - needed_args) -- find application function for the remaining regs/args - , newAp |= hdApply .! newTag + , newAp |= ApplExpr hdApply [newTag] , traceRts cfg (jString "h$ap_gen: next: " + (newAp .^ "n")) -- Drop used registers from the stack. @@ -643,7 +632,7 @@ genericStackApply cfg = closure info body ----------------------------- [ traceRts cfg (jString "h$ap_gen: undersat") -- find PAP entry function corresponding to given_regs count - , p |= hdPaps .! given_regs + , p |= ApplExpr hdPaps [given_regs] -- build PAP payload: R1 + tag + given register values , newTag |= ((needed_regs-given_regs) .<<. 8) .|. (needed_args-given_args) @@ -716,7 +705,7 @@ genericFastApply s = do push_all_regs <- pushAllRegs tag return $ mconcat $ [ push_all_regs - , ap |= hdApply .! tag + , ap |= ApplExpr hdApply [tag] , ifS (ap .===. hdApGen) ((sp |= sp + 2) <> (stack .! (sp-1) |= tag)) (sp |= sp + 1) @@ -750,7 +739,7 @@ genericFastApply s = , traceRts s (jString "h$ap_gen_fast: oversat " + sp) , push_args , newTag |= ((myRegs-( arity.>>.8)).<<.8).|.myAr-ar - , newAp |= hdApply .! newTag + , newAp |= ApplExpr hdApply [newTag] , ifS (newAp .===. hdApGen) ((sp |= sp + 2) <> (stack .! (sp - 1) |= newTag)) (sp |= sp + 1) @@ -761,7 +750,7 @@ genericFastApply s = -- else [traceRts s (jString "h$ap_gen_fast: undersat: " + myRegs + jString " " + tag) , jwhenS (tag .!=. 0) $ mconcat - [ p |= hdPaps .! myRegs + [ p |= ApplExpr hdPaps [myRegs] , dat |= toJExpr [r1, ((arity .>>. 8)-myRegs)*256+ar-myAr] , get_regs , r1 |= initClosure s p dat jCurrentCCS @@ -773,14 +762,24 @@ genericFastApply s = pushAllRegs :: JStgExpr -> JSM JStgStat pushAllRegs tag = jVar \regs -> - return $ mconcat $ - [ regs |= tag .>>. 8 - , sp |= sp + regs - , SwitchStat regs (map pushReg [65,64..2]) mempty - ] - where - pushReg :: Int -> (JStgExpr, JStgStat) - pushReg r = (toJExpr (r-1), stack .! (sp - toJExpr (r - 2)) |= jsReg r) + let max_low_reg = regNumber maxLowReg + low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments + pushReg :: Int -> (JStgExpr, JStgStat) + pushReg r = (toJExpr r, stack .! (sp - toJExpr (r - 2)) |= jsReg r) + in return $ mconcat $ + [ regs |= tag .>>. 8 + , sp |= sp + regs + -- increment the number of regs by 1, so that it matches register + -- numbers (R1 is not used for args) + , postIncrS regs + -- copy high registers with a loop + , WhileStat False (regs .>. toJExpr max_low_reg) $ mconcat + -- rN stored in stack[sp - N - 2] so that r2 is stored in stack[sp], etc. + [ stack .! (sp - regs - 2) |= highReg_expr regs + , postDecrS regs + ] + , SwitchStat regs (map pushReg low_regs) mempty + ] pushArgs :: JStgExpr -> JStgExpr -> JSM JStgStat pushArgs start end = @@ -906,7 +905,7 @@ stackApply s fun_name nargs nvars = [ rs |= (arity .>>. 8) , loadRegs rs , sp |= sp - rs - , newAp |= (hdApply .! ((toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8))) + , newAp |= ApplExpr hdApply [(toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8)] , stack .! sp |= newAp , profStat s pushRestoreCCS , traceRts s (toJExpr (fun_name <> ": new stack frame: ") + (newAp .^ "n")) @@ -989,7 +988,7 @@ fastApply s fun_name nargs nvars = if nargs == 0 && nvars == 0 + rsRemain) , saveRegs rs , sp |= sp + rsRemain + 1 - , stack .! sp |= hdApply .! ((rsRemain.<<.8).|. (toJExpr nargs - mask8 arity)) + , stack .! sp |= ApplExpr hdApply [(rsRemain.<<.8).|. (toJExpr nargs - mask8 arity)] , profStat s pushRestoreCCS , returnS c ] @@ -1238,14 +1237,30 @@ pap s r = closure (ClosureInfo , profStat s (enterCostCentreFun currentCCS) , extra |= (funOrPapArity c (Just f) .>>. 8) - toJExpr r , traceRts s (toJExpr (funcName <> ": pap extra args moving: ") + extra) - , moveBy extra + , case r of + 0 -> mempty -- in pap_0 we don't shift any register + _ -> moveBy extra , loadOwnArgs d , r1 |= c , returnS f ] - moveBy extra = SwitchStat extra - (reverse $ map moveCase [1..maxReg-r-1]) mempty - moveCase m = (toJExpr m, jsReg (m+r+1) |= jsReg (m+1)) + moveBy extra = + let max_low_reg = regNumber maxLowReg + low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments + move_case m = (toJExpr m, jsReg (m+r) |= jsReg m) + in mconcat + [ -- increment the number of args by 1, so that it matches register + -- numbers (R1 is not used for args) + postIncrS extra + -- copy high registers with a loop + , WhileStat False (extra .>. toJExpr max_low_reg) $ mconcat + [ highReg_expr (extra + toJExpr r) |= highReg_expr extra + , postDecrS extra + ] + -- then copy low registers with a case + , SwitchStat extra (map move_case low_regs) mempty + ] + loadOwnArgs d = mconcat $ map (\r -> jsReg (r+1) |= dField d (r+2)) [1..r] dField d n = SelExpr d (name . mkFastString $ ('d':show (n-1))) @@ -1274,7 +1289,9 @@ papGen cfg = (jString "h$pap_gen: expected function or pap") , profStat cfg (enterCostCentreFun currentCCS) , traceRts cfg (jString "h$pap_gen: generic pap extra args moving: " + or) + -- shift newly applied arguments into appropriate registers , appS hdMoveRegs2 [or, r] + -- load stored arguments into lowest argument registers (i.e. starting from R2) , loadOwnArgs d r , r1 |= c , returnS f @@ -1285,9 +1302,22 @@ papGen cfg = funcIdent = name funcName funcName = hdPapGenStr loadOwnArgs d r = - let prop n = d .^ ("d" <> mkFastString (show $ n+1)) - loadOwnArg n = (toJExpr n, jsReg (n+1) |= prop n) - in SwitchStat r (map loadOwnArg [127,126..1]) mempty + let prop n = d .^ (mkFastString ("d" ++ show n)) + loadOwnArg n = (toJExpr n, jsReg n |= prop n) + max_low_reg = regNumber maxLowReg + low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments + in mconcat + [ -- increment the number of args by 1, so that it matches register + -- numbers (R1 is not used for args) and PAP fields (starting from d2) + postIncrS r + -- copy high registers with a loop + , WhileStat False (r .>. toJExpr max_low_reg) $ mconcat + [ highReg_expr r |= (d .! (jString (fsLit "d") + r)) + , postDecrS r + ] + -- then copy low registers with a case. + , SwitchStat r (map loadOwnArg low_regs) mempty + ] -- general utilities -- move the first n registers, starting at R2, m places up (do not use with negative m) @@ -1301,7 +1331,7 @@ moveRegs2 = jFunction (name hdMoveRegs2) moveSwitch switchCase n m = (toJExpr $ (n `Bits.shiftL` 8) Bits..|. m , mconcat (map (`moveRegFast` m) [n+1,n..2]) - <> BreakStat Nothing {-[j| break; |]-}) + <> BreakStat Nothing) moveRegFast n m = jsReg (n+m) |= jsReg n -- fallback defaultCase n m = ===================================== compiler/GHC/StgToJS/Expr.hs ===================================== @@ -312,7 +312,7 @@ genBody ctx startReg args e typ = do -- load arguments into local variables la <- do args' <- concatMapM genIdArgI args - return (declAssignAll args' (fmap toJExpr [startReg..])) + return (declAssignAll args' (jsRegsFrom startReg)) -- assert that arguments have valid runtime reps lav <- verifyRuntimeReps args @@ -665,7 +665,7 @@ genCase ctx bnd e at alts l | otherwise = do rj <- genRet ctx bnd at alts l let ctx' = ctxSetTop bnd - $ ctxSetTarget (assocIdExprs bnd (map toJExpr [R1 ..])) + $ ctxSetTarget (assocIdExprs bnd jsRegsFromR1) $ ctx (ej, _r) <- genExpr ctx' e return (rj <> ej, ExprCont) @@ -730,7 +730,7 @@ genRet ctx e at as l = freshIdent >>= f fun free = resetSlots $ do decs <- declVarsForId e - load <- flip assignAll (map toJExpr [R1 ..]) . map toJExpr <$> identsForId e + load <- flip assignAll jsRegsFromR1 . map toJExpr <$> identsForId e loadv <- verifyRuntimeReps [e] ras <- loadRetArgs free rasv <- verifyRuntimeReps (map (\(x,_,_)->x) free) ===================================== compiler/GHC/StgToJS/Regs.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} module GHC.StgToJS.Regs ( StgReg (..) @@ -6,17 +7,25 @@ module GHC.StgToJS.Regs , sp , stack , r1, r2, r3, r4 + , pattern R1, pattern R2, pattern R3, pattern R4 , regsFromR1 , regsFromR2 + , regsFromTo + , jsRegsFrom , jsRegsFromR1 , jsRegsFromR2 , StgRet (..) - , jsRegToInt - , intToJSReg + , regNumber , jsReg + , highReg + , highReg_expr , maxReg + , maxLowReg , minReg + , minHighReg , lowRegs + , lowRegsCount + , lowRegsIdents , retRegs , register , foreignRegister @@ -32,6 +41,7 @@ import GHC.JS.Make import GHC.StgToJS.Symbols import GHC.Data.FastString +import GHC.Utils.Panic.Plain import Data.Array import qualified Data.ByteString.Char8 as BSC @@ -39,26 +49,15 @@ import Data.Char import Data.Semigroup ((<>)) -- | General purpose "registers" --- --- The JS backend arbitrarily supports 128 registers -data StgReg - = R1 | R2 | R3 | R4 | R5 | R6 | R7 | R8 - | R9 | R10 | R11 | R12 | R13 | R14 | R15 | R16 - | R17 | R18 | R19 | R20 | R21 | R22 | R23 | R24 - | R25 | R26 | R27 | R28 | R29 | R30 | R31 | R32 - | R33 | R34 | R35 | R36 | R37 | R38 | R39 | R40 - | R41 | R42 | R43 | R44 | R45 | R46 | R47 | R48 - | R49 | R50 | R51 | R52 | R53 | R54 | R55 | R56 - | R57 | R58 | R59 | R60 | R61 | R62 | R63 | R64 - | R65 | R66 | R67 | R68 | R69 | R70 | R71 | R72 - | R73 | R74 | R75 | R76 | R77 | R78 | R79 | R80 - | R81 | R82 | R83 | R84 | R85 | R86 | R87 | R88 - | R89 | R90 | R91 | R92 | R93 | R94 | R95 | R96 - | R97 | R98 | R99 | R100 | R101 | R102 | R103 | R104 - | R105 | R106 | R107 | R108 | R109 | R110 | R111 | R112 - | R113 | R114 | R115 | R116 | R117 | R118 | R119 | R120 - | R121 | R122 | R123 | R124 | R125 | R126 | R127 | R128 - deriving (Eq, Ord, Show, Enum, Bounded, Ix) +newtype StgReg + = StgReg Int + deriving (Eq,Ord,Ix) + +pattern R1, R2, R3, R4 :: StgReg +pattern R1 = StgReg 0 +pattern R2 = StgReg 1 +pattern R3 = StgReg 2 +pattern R4 = StgReg 3 -- | Stack registers data Special @@ -78,7 +77,7 @@ instance ToJExpr Special where toJExpr Sp = hdStackPtr instance ToJExpr StgReg where - toJExpr r = registers ! r + toJExpr r = register r instance ToJExpr StgRet where toJExpr r = rets ! r @@ -99,25 +98,42 @@ r2 = toJExpr R2 r3 = toJExpr R3 r4 = toJExpr R4 +-- | 1-indexed register number (R1 has index 1) +regNumber :: StgReg -> Int +regNumber (StgReg r) = r+1 -jsRegToInt :: StgReg -> Int -jsRegToInt = (+1) . fromEnum +-- | StgReg from 1-indexed number +regFromNumber :: Int -> StgReg +regFromNumber r = assert (r >= 1) $ StgReg (r-1) -intToJSReg :: Int -> StgReg -intToJSReg r = toEnum (r - 1) +regsFromTo :: StgReg -> StgReg -> [StgReg] +regsFromTo (StgReg x) (StgReg y) = map StgReg [x .. y] +-- | Register expression from its 1-indexed index jsReg :: Int -> JStgExpr -jsReg r = toJExpr (intToJSReg r) +jsReg r = toJExpr (regFromNumber r) + +minReg :: StgReg +minReg = R1 -maxReg :: Int -maxReg = jsRegToInt maxBound +maxReg :: StgReg +maxReg = regFromNumber maxBound -minReg :: Int -minReg = jsRegToInt minBound +lowRegsCount :: Int +lowRegsCount = 31 + +maxLowReg :: StgReg +maxLowReg = regFromNumber lowRegsCount + +-- | First register stored in h$regs array instead of having its own top-level +-- variable +minHighReg :: StgReg +minHighReg = case maxLowReg of + StgReg r -> StgReg (r+1) -- | List of registers, starting from R1 regsFromR1 :: [StgReg] -regsFromR1 = enumFrom R1 +regsFromR1 = regsFromTo R1 maxReg ++ repeat (panic "StgToJS: code requires too many registers") -- | List of registers, starting from R2 regsFromR2 :: [StgReg] @@ -131,35 +147,59 @@ jsRegsFromR1 = fmap toJExpr regsFromR1 jsRegsFromR2 :: [JStgExpr] jsRegsFromR2 = tail jsRegsFromR1 +-- | List of registers, starting from given reg as JExpr +jsRegsFrom :: StgReg -> [JStgExpr] +jsRegsFrom (StgReg n) = drop n jsRegsFromR1 + +-- | High register +highReg :: Int -> JStgExpr +highReg r = assert (r >= regNumber minHighReg) $ IdxExpr hdRegs (toJExpr (r - regNumber minHighReg)) + +-- | High register indexing with a JS expression +highReg_expr :: JStgExpr -> JStgExpr +highReg_expr r = IdxExpr hdRegs (r - toJExpr (regNumber minHighReg)) + + --------------------------------------------------- -- caches --------------------------------------------------- -lowRegs :: [Ident] -lowRegs = map reg_to_ident [R1 .. R31] - where reg_to_ident = name . mkFastString . (unpackFS hdStr ++) . map toLower . show +lowRegs :: [StgReg] +lowRegs = regsFromTo minReg maxLowReg + +lowRegsIdents :: [Ident] +lowRegsIdents = map reg_to_ident lowRegs + where + -- low regs are named h$r1, h$r2, etc. + reg_to_ident r = name (mkFastString (unpackFS hdStr ++ "r" ++ show (regNumber r))) retRegs :: [Ident] retRegs = [name . mkFastStringByteString $ hdB <> BSC.pack (map toLower $ show n) | n <- enumFrom Ret1] --- cache JExpr representing StgReg -registers :: Array StgReg JStgExpr -registers = listArray (minBound, maxBound) (map (global . identFS) lowRegs ++ map regN [R32 .. R128]) - where - regN :: StgReg -> JStgExpr - regN r = IdxExpr hdRegs (toJExpr (fromEnum r - 32)) - -- cache JExpr representing StgRet rets :: Array StgRet JStgExpr rets = listArray (minBound, maxBound) (map retN (enumFrom Ret1)) where retN = global . mkFastString . (unpackFS hdStr ++) . map toLower . show --- | Given a register, return the JS syntax object representing that register -register :: StgReg -> JStgExpr -register i = registers ! i - -- | Given a register, return the JS syntax object representing that register foreignRegister :: StgRet -> JStgExpr foreignRegister i = rets ! i + +-- | Given a register, return the JS syntax object representing that register +register :: StgReg -> JStgExpr +register i + | i <= maxCachedReg = register_cache ! i -- Expressions of common registers are cached. + | otherwise = make_high_reg i -- Expression of higher registers are made on the fly + +maxCachedReg :: StgReg +maxCachedReg = regFromNumber 128 + +-- cache JExpr representing StgReg +register_cache :: Array StgReg JStgExpr +register_cache = listArray (minReg, maxCachedReg) (map (global . identFS) lowRegsIdents ++ map make_high_reg (regsFromTo minHighReg maxCachedReg)) + +-- | Make h$regs[XXX] expression for the register +make_high_reg :: StgReg -> JStgExpr +make_high_reg r = highReg (regNumber r) ===================================== compiler/GHC/StgToJS/Rts/Rts.hs ===================================== @@ -54,7 +54,12 @@ import qualified Data.Bits as Bits -- | The garbageCollector resets registers and result variables. garbageCollector :: JSM JStgStat garbageCollector = jBlock - [ jFunction' hdResetRegisters (return $ mconcat $ map resetRegister [minBound..maxBound]) + [ jFunction' hdResetRegisters $ return $ mconcat + [ -- reset low registers explicitly + mconcat (map resetRegister lowRegs) + -- reset the whole h$regs array with h$regs.fill(null) + , toStat $ ApplExpr (hdRegs .^ "fill") [null_] + ] , jFunction' hdResetResultVars (return $ mconcat $ map resetResultVar [minBound..maxBound]) ] @@ -249,7 +254,7 @@ declRegs = do loaders <- loadRegs return $ mconcat [ hdRegsStr ||= toJExpr (JList []) - , mconcat (map declReg lowRegs) + , mconcat (map declReg lowRegsIdents) , getters_setters , loaders ] @@ -259,15 +264,15 @@ declRegs = do -- | JS payload to define getters and setters on the registers. regGettersSetters :: JSM JStgStat regGettersSetters = - do setters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases mempty) - getters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) mempty) + do getters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases (defaultGetRegCase n)) + setters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) (defaultSetRegCase n v)) return $ setters <> getters where - getRegCases = - map (\r -> (toJExpr (jsRegToInt r) , returnS (toJExpr r))) regsFromR1 - setRegCases :: JStgExpr -> [(JStgExpr,JStgStat)] - setRegCases v = - map (\r -> (toJExpr (jsRegToInt r), (toJExpr r |= toJExpr v) <> returnS undefined_)) regsFromR1 + getRegCases = map (\r -> (toJExpr (regNumber r) , returnS (toJExpr r))) lowRegs + defaultGetRegCase n = returnS (highReg_expr n) + + setRegCases v = map (\r -> (toJExpr (regNumber r), (toJExpr r |= v) <> BreakStat Nothing)) lowRegs + defaultSetRegCase n v = highReg_expr n |= v -- | JS payload that defines the functions to load each register loadRegs :: JSM JStgStat ===================================== compiler/GHC/StgToJS/Rts/Types.hs ===================================== @@ -69,12 +69,3 @@ stackFrameSize tgt f = (tgt |= mask8 tag + 1) -- else set to mask'd tag + 1 ] )) - - -------------------------------------------------------------------------------- --- Register utilities --------------------------------------------------------------------------------- - --- | Perform the computation 'f', on the range of registers bounded by 'start' --- and 'end'. -withRegs :: StgReg -> StgReg -> (StgReg -> JStgStat) -> JStgStat -withRegs start end f = mconcat $ fmap f [start..end] ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -256,4 +256,4 @@ test('T24893', normal, compile_and_run, ['-O']) test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c']) test('T25364', normal, compile_and_run, ['']) test('T26061', normal, compile_and_run, ['']) -test('T26537', js_broken(26558), compile_and_run, ['-O2 -fregs-graph']) +test('T26537', normal, compile_and_run, ['-O2 -fregs-graph']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0a1e5748d90c1cbd2e6a90ccbe7d96... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0a1e5748d90c1cbd2e6a90ccbe7d96... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)