[Git][ghc/ghc][wip/js-rts-fixmes] JS RTS: use jsClosureCount for closureConstructors and cache sizes
Josh Meredith (@JoshMeredith)
gitlab at gitlab.haskell.org
Wed Feb 8 10:15:44 UTC 2023
Josh Meredith pushed to branch wip/js-rts-fixmes at Glasgow Haskell Compiler / GHC
Commits:
1496d749 by Josh Meredith at 2023-02-08T10:15:25+00:00
JS RTS: use jsClosureCount for closureConstructors and cache sizes
- - - - -
2 changed files:
- compiler/GHC/JS/Make.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
Changes:
=====================================
compiler/GHC/JS/Make.hs
=====================================
@@ -133,6 +133,7 @@ module GHC.JS.Make
, clsName
, dataFieldName, dataFieldNames
, varName, varNames
+ , jsClosureCount
)
where
@@ -642,10 +643,13 @@ instance Fractional JExpr where
-- | Cache "dXXX" field names
dataFieldCache :: Array Int FastString
-dataFieldCache = listArray (0,nFieldCache) (map (mkFastString . ('d':) . show) [(0::Int)..nFieldCache])
+dataFieldCache = listArray (0,jsClosureCount) (map (mkFastString . ('d':) . show) [(0::Int)..nFieldCache])
nFieldCache :: Int
-nFieldCache = 16384
+nFieldCache = 128
+
+jsClosureCount :: Int
+jsClosureCount = 24
dataFieldName :: Int -> FastString
dataFieldName i
@@ -653,44 +657,44 @@ dataFieldName i
| otherwise = dataFieldCache ! i
dataFieldNames :: [FastString]
-dataFieldNames = fmap dataFieldName [1..nFieldCache]
+dataFieldNames = fmap dataFieldName [1..jsClosureCount]
-- | Cache "h$dXXX" names
dataCache :: Array Int FastString
-dataCache = listArray (0,63) (map (mkFastString . ("h$d"++) . show) [(0::Int)..63])
+dataCache = listArray (0,nFieldCache) (map (mkFastString . ("h$d"++) . show) [(0::Int)..nFieldCache])
dataName :: Int -> FastString
dataName i
- | i < 0 || i > 63 = panic "dataCacheName" (ppr i)
- | otherwise = dataCache ! i
+ | i < 0 || i > nFieldCache = panic "dataCacheName" (ppr i)
+ | otherwise = dataCache ! i
allocData :: Int -> JExpr
allocData i = toJExpr (TxtI (dataCache ! i))
-- | Cache "h$cXXX" names
clsCache :: Array Int FastString
-clsCache = listArray (0,63) (map (mkFastString . ("h$c"++) . show) [(0::Int)..63])
+clsCache = listArray (0,jsClosureCount) (map (mkFastString . ("h$c"++) . show) [(0::Int)..jsClosureCount])
clsName :: Int -> FastString
clsName i
- | i < 0 || i > 63 = panic "clsCacheName" (ppr i)
- | otherwise = clsCache ! i
+ | i < 0 || i > jsClosureCount = panic "clsCacheName" (ppr i)
+ | otherwise = clsCache ! i
allocClsA :: Int -> JExpr
allocClsA i = toJExpr (TxtI (clsCache ! i))
-- | Cache "xXXX" names
varCache :: Array Int FastString
-varCache = listArray (0,63) (map (mkFastString . ('x':) . show) [(0::Int)..63])
+varCache = listArray (0,jsClosureCount) (map (mkFastString . ('x':) . show) [(0::Int)..jsClosureCount])
varName :: Int -> Ident
varName i
- | i < 0 || i > 63 = panic "varCacheName" (ppr i)
- | otherwise = TxtI $ varCache ! i
+ | i < 0 || i > jsClosureCount = panic "varCacheName" (ppr i)
+ | otherwise = TxtI $ varCache ! i
varNames :: [Ident]
-varNames = fmap varName [1..63]
+varNames = fmap varName [1..jsClosureCount]
--------------------------------------------------------------------------------
=====================================
compiler/GHC/StgToJS/Rts/Rts.hs
=====================================
@@ -81,8 +81,8 @@ resetResultVar r = toJExpr r |= null_
-- JIT can optimize better.
closureConstructors :: StgToJSConfig -> JStat
closureConstructors s = BlockStat
- [ mconcat (map mkClosureCon (Nothing : map Just [0..24]))
- , mconcat (map mkDataFill [1..24])
+ [ mconcat (map mkClosureCon (Nothing : map Just [0..jsClosureCount]))
+ , mconcat (map mkDataFill [1..jsClosureCount])
]
where
prof = csProf s
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1496d749fa2fea75870d23a116918ccdcec43bca
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1496d749fa2fea75870d23a116918ccdcec43bca
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230208/e60ecf93/attachment-0001.html>
More information about the ghc-commits
mailing list