[Git][ghc/ghc][wip/T23479] 3 commits: git: remove a.out and include it in .gitignore

Serge S. Gulin (@gulin.serge) gitlab at gitlab.haskell.org
Sat Aug 24 06:18:53 UTC 2024



Serge S. Gulin pushed to branch wip/T23479 at Glasgow Haskell Compiler / GHC


Commits:
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
38c6b2d6 by Serge S. Gulin at 2024-08-24T09:06:24+03:00
JS: Re-add optimization for literal strings (fixes #23479)

- - - - -


4 changed files:

- .gitignore
- − a.out
- compiler/GHC/StgToJS/Apply.hs
- docs/users_guide/exts/multiline_strings.rst


Changes:

=====================================
.gitignore
=====================================
@@ -35,6 +35,7 @@ Thumbs.db
 __pycache__
 .mypy_cache
 *.SYMDEF*
+a.out
 
 log
 tags


=====================================
a.out deleted
=====================================
Binary files a/a.out and /dev/null differ


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -51,6 +52,7 @@ import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Name (nameModule_maybe, OccName (occNameFS), nameOccName)
 
 import GHC.Stg.Syntax
 
@@ -60,6 +62,8 @@ import GHC.Core.TyCon
 import GHC.Core.DataCon
 import GHC.Core.Type hiding (typeSize)
 
+import GHC.Unit.Module (moduleNameFS, GenModule (moduleName), unitIdString, moduleUnitId)
+
 import GHC.Utils.Misc
 import GHC.Utils.Monad
 import GHC.Utils.Panic
@@ -69,6 +73,7 @@ import GHC.Data.FastString
 import qualified Data.Bits as Bits
 import Data.Monoid
 import Data.Array
+import Data.List (isPrefixOf)
 
 -- | Pre-generated functions for fast Apply.
 -- These are bundled with the RTS.
@@ -86,6 +91,13 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
+matchVarName :: String -> FastString -> FastString -> Id -> Bool
+matchVarName pkg modu occ (idName -> n)
+  | Just m <- nameModule_maybe n =
+    occ  == occNameFS (nameOccName n) &&
+    modu == moduleNameFS (moduleName m) &&
+    pkg `isPrefixOf` unitIdString (moduleUnitId m)
+  | otherwise = False
 
 -- | Generate an application of some args to an Id.
 --
@@ -98,6 +110,13 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- special cases for JSString literals
+    -- we could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case
+    | [StgVarArg v] <- args
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    , matchVarName "ghcjs-prim" "GHCJS.Prim" "unsafeUnpackJSStringUtf8##" i
+    = (,ExprInline) . (|=) top . app "h$decodeUtf8z" <$> varsForId v
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
docs/users_guide/exts/multiline_strings.rst
=====================================
@@ -36,7 +36,7 @@ Examples
 +-----------------------+------------------------+---------------------------+
 | Expression            | Output                 | Notes                     |
 +=======================+========================+===========================+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        |                           |
 |    """                |       "Line 1\n"       |                           |
 |    Line 1             |    ++ "Line 2\n"       |                           |
@@ -44,7 +44,7 @@ Examples
 |    Line 3             |                        |                           |
 |    """                |                        |                           |
 +-----------------------+------------------------+---------------------------+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        | Characters on the same    |
 |    """Test            |       "Test\n"         | line as the delimiter are |
 |    Line 1             |    ++ "Line 1\n"       | still included            |
@@ -52,7 +52,7 @@ Examples
 |    Line 3             |    ++ "Line 3\n"       |                           |
 |    """                |                        |                           |
 +-----------------------+------------------------+---------------------------+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        | Omit the trailing newline |
 |    """                |       "Line 1\n"       | with string gaps          |
 |    Line 1             |    ++ "Line 2\n"       |                           |
@@ -60,7 +60,7 @@ Examples
 |    Line 3\            |                        |                           |
 |    \"""               |                        |                           |
 +-----------------------+------------------------+---------------------------+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        | Double quotes don't need  |
 |    """                |       "\"Hello\"\n"    | to be escaped unless      |
 |    "Hello"            |    ++ "\"\"\"\n"       | they're triple quoted     |
@@ -68,7 +68,7 @@ Examples
 |    \"""               |                        |                           |
 |    """                |                        |                           |
 +-----------------------+------------------------+---------------------------+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        | Only common indentation   |
 |    """                |       "<div>\n"        | is stripped               |
 |      <div>            |    ++ "  <p>ABC</p>\n" |                           |
@@ -76,7 +76,7 @@ Examples
 |      </div>           |                        |                           |
 |    """                |                        |                           |
 +-----------------------+------------------------+---------------------------+
-| .. code-block:: text  | .. code-block::        |                           |
+| .. code-block:: text  | ::                     |                           |
 |                       |                        | Use ``\&`` to keep        |
 |    """                |       "  Line 1\n"     | leading indentation for   |
 |      \&  Line 1       |    ++ "  Line 2\n"     | each line                 |



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12e72c6827c312ac3d7c489a9af48aee7f302e3f...38c6b2d60c3d43296447cb765e3fa164c1489a09

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12e72c6827c312ac3d7c489a9af48aee7f302e3f...38c6b2d60c3d43296447cb765e3fa164c1489a09
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/20240824/4ac7ed32/attachment-0001.html>


More information about the ghc-commits mailing list