[Git][ghc/ghc][wip/js-rts-fixmes] Factor JS Rts generation for h$c{_,0,1,2} into h$c{n} and improve name caching

Josh Meredith (@JoshMeredith) gitlab at gitlab.haskell.org
Tue Feb 14 16:06:21 UTC 2023



Josh Meredith pushed to branch wip/js-rts-fixmes at Glasgow Haskell Compiler / GHC


Commits:
141cba6d by Josh Meredith at 2023-02-14T16:05:32+00:00
Factor JS Rts generation for h$c{_,0,1,2} into h$c{n} and improve name caching

- - - - -


4 changed files:

- compiler/GHC/JS/Make.hs
- compiler/GHC/StgToJS/DataCon.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Rts/Rts.hs


Changes:

=====================================
compiler/GHC/JS/Make.hs
=====================================
@@ -129,7 +129,11 @@ module GHC.JS.Make
   -- * Miscellaneous
   -- $misc
   , allocData, allocClsA
-  , dataFieldName, dataFieldNames
+  , dataName
+  , clsName
+  , dataFieldName
+  , varName
+  , jsClosureCount
   )
 where
 
@@ -142,10 +146,8 @@ import Control.Arrow ((***))
 import Data.Array
 import qualified Data.Map as M
 
-import GHC.Utils.Outputable (Outputable (..))
 import GHC.Data.FastString
 import GHC.Utils.Monad.State.Strict
-import GHC.Utils.Panic
 import GHC.Utils.Misc
 import GHC.Types.Unique.Map
 
@@ -641,31 +643,52 @@ instance Fractional JExpr where
 dataFieldCache :: Array Int FastString
 dataFieldCache = listArray (0,nFieldCache) (map (mkFastString . ('d':) . show) [(0::Int)..nFieldCache])
 
+-- | Data names are used in the AST, and logging has determined that 255 is the maximum number we see.
 nFieldCache :: Int
-nFieldCache  = 16384
+nFieldCache  = 255
+
+-- | We use this in the RTS to determine the number of generated closures. These closures use the names
+-- cached here, so we bind them to the same number.
+jsClosureCount :: Int
+jsClosureCount  = 24
 
 dataFieldName :: Int -> FastString
 dataFieldName i
-  | i < 1 || i > nFieldCache = panic "dataFieldName" (ppr i)
+  | i < 0 || i > nFieldCache = mkFastString ('d' : show i)
   | otherwise                = dataFieldCache ! i
 
-dataFieldNames :: [FastString]
-dataFieldNames = fmap dataFieldName [1..nFieldCache]
-
-
 -- | Cache "h$dXXX" names
 dataCache :: Array Int FastString
-dataCache = listArray (0,1024) (map (mkFastString . ("h$d"++) . show) [(0::Int)..1024])
+dataCache = listArray (0,jsClosureCount) (map (mkFastString . ("h$d"++) . show) [(0::Int)..jsClosureCount])
+
+dataName :: Int -> FastString
+dataName i
+  | i < 0 || i > nFieldCache = mkFastString ("h$d" ++ show i)
+  | otherwise                = dataCache ! i
 
 allocData :: Int -> JExpr
-allocData i = toJExpr (TxtI (dataCache ! i))
+allocData i = toJExpr (TxtI (dataName i))
 
 -- | Cache "h$cXXX" names
 clsCache :: Array Int FastString
-clsCache = listArray (0,1024) (map (mkFastString . ("h$c"++) . show) [(0::Int)..1024])
+clsCache = listArray (0,jsClosureCount) (map (mkFastString . ("h$c"++) . show) [(0::Int)..jsClosureCount])
+
+clsName :: Int -> FastString
+clsName i
+  | i < 0 || i > jsClosureCount = mkFastString ("h$c" ++ show i)
+  | otherwise                   = clsCache ! i
 
 allocClsA :: Int -> JExpr
-allocClsA i = toJExpr (TxtI (clsCache ! i))
+allocClsA i = toJExpr (TxtI (clsName i))
+
+-- | Cache "xXXX" names
+varCache :: Array Int Ident
+varCache = listArray (0,jsClosureCount) (map (TxtI . mkFastString . ('x':) . show) [(0::Int)..jsClosureCount])
+
+varName :: Int -> Ident
+varName i
+  | i < 0 || i > jsClosureCount = TxtI $ mkFastString ('x' : show i)
+  | otherwise                   = varCache ! i
 
 
 --------------------------------------------------------------------------------


=====================================
compiler/GHC/StgToJS/DataCon.hs
=====================================
@@ -97,7 +97,7 @@ allocDynamicE :: Bool          -- ^ csInlineAlloc from StgToJSConfig
               -> Maybe JExpr
               -> JExpr
 allocDynamicE  inline_alloc entry free cc
-  | inline_alloc || length free > 24 = newClosure $ Closure
+  | inline_alloc || length free > jsClosureCount = newClosure $ Closure
       { clEntry  = entry
       , clField1 = fillObj1
       , clField2 = fillObj2


=====================================
compiler/GHC/StgToJS/Expr.hs
=====================================
@@ -1006,7 +1006,7 @@ allocDynAll haveDecl middle cls = do
                         ]
             (ex:es)  -> mconcat
                         [ toJExpr i .^ closureField1_ |= toJExpr ex
-                        , toJExpr i .^ closureField2_ |= toJExpr (jhFromList (zip dataFieldNames es))
+                        , toJExpr i .^ closureField2_ |= toJExpr (jhFromList (zip (map dataFieldName [1..]) es))
                         ]
       | otherwise = case es of
             []      -> mempty


=====================================
compiler/GHC/StgToJS/Rts/Rts.hs
=====================================
@@ -81,36 +81,8 @@ resetResultVar r = toJExpr r |= null_
 -- JIT can optimize better.
 closureConstructors :: StgToJSConfig -> JStat
 closureConstructors s = BlockStat
-  [ declClsConstr "h$c" ["f"] $ Closure
-      { clEntry  = var "f"
-      , clField1 = null_
-      , clField2 = null_
-      , clMeta   = 0
-      , clCC     = ccVal
-      }
-  , declClsConstr "h$c0" ["f"] $ Closure
-      { clEntry  = var "f"
-      , clField1 = null_
-      , clField2 = null_
-      , clMeta   = 0
-      , clCC     = ccVal
-      }
-  , declClsConstr "h$c1" ["f", "x1"] $ Closure
-      { clEntry  = var "f"
-      , clField1 = var "x1"
-      , clField2 = null_
-      , clMeta   = 0
-      , clCC     = ccVal
-      }
-  , declClsConstr "h$c2" ["f", "x1", "x2"] $ Closure
-      { clEntry  = var "f"
-      , clField1 = var "x1"
-      , clField2 = var "x2"
-      , clMeta   = 0
-      , clCC     = ccVal
-      }
-  , mconcat (map mkClosureCon [3..24])
-  , mconcat (map mkDataFill [1..24])
+  [ mconcat (map mkClosureCon (Nothing : map Just [0..jsClosureCount]))
+  , mconcat (map mkDataFill [1..jsClosureCount])
   ]
   where
     prof = csProf s
@@ -118,19 +90,8 @@ closureConstructors s = BlockStat
       -- the cc argument happens to be named just like the cc field...
       | prof      = ([TxtI closureCC_], Just (var closureCC_))
       | otherwise = ([], Nothing)
-    addCCArg as = map TxtI as ++ ccArg
     addCCArg' as = as ++ ccArg
 
-    declClsConstr i as cl = TxtI i ||= ValExpr (JFunc (addCCArg as)
-      ( jVar $ \x ->
-          [ checkC
-          , x |= newClosure cl
-          , notifyAlloc x
-          , traceAlloc x
-          , returnS x
-          ]
-         ))
-
     traceAlloc x | csTraceRts s = appS "h$traceAlloc" [x]
                  | otherwise    = mempty
 
@@ -172,26 +133,36 @@ closureConstructors s = BlockStat
 
            | otherwise = mempty
 
-    mkClosureCon :: Int -> JStat
-    mkClosureCon n = funName ||= toJExpr fun
+    mkClosureCon :: Maybe Int -> JStat
+    mkClosureCon n0 = funName ||= toJExpr fun
       where
-        funName = TxtI $ mkFastString ("h$c" ++ show n)
+        n | Just n' <- n0 = n'
+          | Nothing <- n0 = 0
+        funName | Just n' <- n0 = TxtI $ clsName n'
+                | Nothing <- n0 = TxtI $ mkFastString "h$c"
         -- args are: f x1 x2 .. xn [cc]
-        args   = TxtI "f" : addCCArg' (map (TxtI . mkFastString . ('x':) . show) [(1::Int)..n])
+        args   = TxtI "f" : addCCArg' (map varName [1..n])
         fun    = JFunc args funBod
         -- x1 goes into closureField1. All the other args are bundled into an
         -- object in closureField2: { d1 = x2, d2 = x3, ... }
         --
-        extra_args = ValExpr . JHash . listToUniqMap $ zip
-                   (map (mkFastString . ('d':) . show) [(1::Int)..])
-                   (map (toJExpr . TxtI . mkFastString . ('x':) . show) [2..n])
+        vars   = map (toJExpr . varName) [1..n]
+
+        x1     = case vars of
+                   []  -> null_
+                   x:_ -> x
+        x2     = case vars of
+                   []     -> null_
+                   [_]    -> null_
+                   [_,x]  -> x
+                   _:x:xs -> ValExpr . JHash . listToUniqMap $ zip (map dataFieldName [1..]) (x:xs)
 
         funBod = jVar $ \x ->
             [ checkC
             , x |= newClosure Closure
                { clEntry  = var "f"
-               , clField1 = var "x1"
-               , clField2 = extra_args
+               , clField1 = x1
+               , clField2 = x2
                , clMeta   = 0
                , clCC     = ccVal
                }
@@ -203,8 +174,8 @@ closureConstructors s = BlockStat
     mkDataFill :: Int -> JStat
     mkDataFill n = funName ||= toJExpr fun
       where
-        funName    = TxtI $ mkFastString ("h$d" ++ show n)
-        ds         = map (mkFastString . ('d':) . show) [(1::Int)..n]
+        funName    = TxtI $ dataName n
+        ds         = map dataFieldName [1..n]
         extra_args = ValExpr . JHash . listToUniqMap . zip ds $ map (toJExpr . TxtI) ds
         fun        = JFunc (map TxtI ds) (checkD <> returnS extra_args)
 
@@ -215,7 +186,7 @@ stackManip = mconcat (map mkPush [1..32]) <>
   where
     mkPush :: Int -> JStat
     mkPush n = let funName = TxtI $ mkFastString ("h$p" ++ show n)
-                   as      = map (TxtI . mkFastString . ('x':) . show) [1..n]
+                   as      = map varName [1..n]
                    fun     = JFunc as ((sp |= sp + toJExpr n)
                                        <> mconcat (zipWith (\i a -> stack .! (sp - toJExpr (n-i)) |= toJExpr a)
                                                    [1..] as))
@@ -228,7 +199,7 @@ stackManip = mconcat (map mkPush [1..32]) <>
                       bits    = bitsIdx sig
                       n       = length bits
                       h       = last bits
-                      args    = map (TxtI . mkFastString . ('x':) . show) [1..n]
+                      args    = map varName [1..n]
                       fun     = JFunc args $
                         mconcat [ sp |= sp + toJExpr (h+1)
                                 , mconcat (zipWith (\b a -> stack .! (sp - toJExpr (h-b)) |= toJExpr a) bits args)
@@ -288,7 +259,7 @@ loadRegs :: JStat
 loadRegs = mconcat $ map mkLoad [1..32]
   where
     mkLoad :: Int -> JStat
-    mkLoad n = let args   = map (TxtI . mkFastString . ("x"++) . show) [1..n]
+    mkLoad n = let args   = map varName [1..n]
                    assign = zipWith (\a r -> toJExpr r |= toJExpr a)
                               args (reverse $ take n regsFromR1)
                    fname  = TxtI $ mkFastString ("h$l" ++ show n)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/141cba6d53b706b65bb6b583aa8b7c3a7c9ac08d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/141cba6d53b706b65bb6b583aa8b7c3a7c9ac08d
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/20230214/37e1b283/attachment-0001.html>


More information about the ghc-commits mailing list