[Git][ghc/ghc][master] 2 commits: Lexer: small perf changes
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Mar 22 01:03:03 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00
Lexer: small perf changes
- Use unsafeChr because we know our values to be valid
- Remove some unnecessary use of `ord` (return Word8 values directly)
- - - - -
864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00
JS: fix some comments
- - - - -
2 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/StgToJS/Linker/Linker.hs
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -2814,19 +2814,19 @@ characters into single bytes.
{-# INLINE adjustChar #-}
adjustChar :: Char -> Word8
-adjustChar c = fromIntegral $ ord adj_c
- where non_graphic = '\x00'
- upper = '\x01'
- lower = '\x02'
- digit = '\x03'
- symbol = '\x04'
- space = '\x05'
- other_graphic = '\x06'
- uniidchar = '\x07'
+adjustChar c = adj_c
+ where non_graphic = 0x00
+ upper = 0x01
+ lower = 0x02
+ digit = 0x03
+ symbol = 0x04
+ space = 0x05
+ other_graphic = 0x06
+ uniidchar = 0x07
adj_c
| c <= '\x07' = non_graphic
- | c <= '\x7f' = c
+ | c <= '\x7f' = fromIntegral (ord c)
-- Alex doesn't handle Unicode, so when Unicode
-- character is encountered we output these values
-- with the actual character value hidden in the state.
@@ -2866,15 +2866,18 @@ adjustChar c = fromIntegral $ ord adj_c
--
-- See Note [Unicode in Alex] and #13986.
alexInputPrevChar :: AlexInput -> Char
-alexInputPrevChar (AI _ buf) = chr (fromIntegral (adjustChar pc))
+alexInputPrevChar (AI _ buf) = unsafeChr (fromIntegral (adjustChar pc))
where pc = prevChar buf '\n'
+unsafeChr :: Int -> Char
+unsafeChr (I# c) = C# (chr# c)
+
-- backwards compatibility for Alex 2.x
alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar inp = case alexGetByte inp of
Nothing -> Nothing
Just (b,i) -> c `seq` Just (c,i)
- where c = chr $ fromIntegral b
+ where c = unsafeChr $ fromIntegral b
-- See Note [Unicode in Alex]
alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -738,7 +738,7 @@ writeExterns out = writeFile (out </> "all.js.externs")
-- | Get all block dependencies for a given set of roots
--
--- Returns the update block info map and the blocks.
+-- Returns the updated block info map and the blocks.
getDeps :: Map Module LocatedBlockInfo -- ^ Block info per module
-> (Module -> IO LocatedBlockInfo) -- ^ Used to load block info if missing
-> Set ExportedFun -- ^ start here
@@ -754,7 +754,7 @@ getDeps init_infos load_info root_funs root_blocks = traverse_funs init_infos S.
-- 1. We use the BlockInfos to find the block corresponding to every
-- exported root functions.
--
- -- 2. We had these blocks to the set of root_blocks if they aren't already
+ -- 2. We add these blocks to the set of root_blocks if they aren't already
-- added to the result.
--
-- 3. Then we traverse the root_blocks to find their dependencies and we
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52072f8e2121fe49a8367027efa3d8db32325f84...864922ef8ab97ea6dfe970be69f0c2fa78315b08
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52072f8e2121fe49a8367027efa3d8db32325f84...864922ef8ab97ea6dfe970be69f0c2fa78315b08
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/20240321/eb401309/attachment-0001.html>
More information about the ghc-commits
mailing list